hydra-cardano-api-0.16.0: A Haskell API for Cardano, tailored to the Hydra project.
Safe HaskellSafe-Inferred
LanguageGHC2021

Hydra.Cardano.Api

Description

A Haskell API for Cardano, tailored to the Hydra project.

This package provides a wrapper around the cardano-ledger, cardano-api and plutus libraries with extra utilities and function commonly used across the Hydra project.

NOTE: We always use the **latest era** available in our codebase, so to ease type signatures and notations, we specialize any type of the cardano-api normally parameterized by an era to the latest era Era. As a consequence, we've defined pattern synonyms for most constructors in the cardano-api to also get rid of era witnesses.

NOTE: This module also uses the **latest plutus version** available (currently PlutusScriptVersion). So make sure that you give it a plutus script of the right version (e.g. when compiling and serializing plutus-tx).

Synopsis

Common type-alias

data StandardCrypto #

Instances

Instances details
Crypto StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

Associated Types

type HASH StandardCrypto

type ADDRHASH StandardCrypto

type DSIGN StandardCrypto

type KES StandardCrypto

type VRF StandardCrypto

PraosCrypto StandardCrypto 
Instance details

Defined in Cardano.Protocol.TPraos.API

PraosCrypto StandardCrypto 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

(CardanoHardForkConstraints StandardCrypto, IOLike m) => Protocol m (CardanoBlock StandardCrypto) 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolInfoArgs (CardanoBlock StandardCrypto) #

Methods

protocolInfo :: ProtocolInfoArgs (CardanoBlock StandardCrypto) -> (ProtocolInfo (CardanoBlock StandardCrypto), m [BlockForging m (CardanoBlock StandardCrypto)]) #

(IOLike m, LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))) => Protocol m (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) #

Methods

protocolInfo :: ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) -> (ProtocolInfo (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley), m [BlockForging m (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley)]) #

ConvertLedgerEvent (HardForkBlock (CardanoEras StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (HardForkBlock (CardanoEras StandardCrypto)) -> Maybe LedgerEvent #

CardanoHardForkConstraints StandardCrypto => ProtocolClient (CardanoBlock StandardCrypto) 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolClientInfoArgs (CardanoBlock StandardCrypto)

Methods

protocolClientInfo :: ProtocolClientInfoArgs (CardanoBlock StandardCrypto) -> ProtocolClientInfo (CardanoBlock StandardCrypto)

ConvertLedgerEvent (ShelleyBlock protocol (AllegraEra StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (AllegraEra StandardCrypto)) -> Maybe LedgerEvent #

ConvertLedgerEvent (ShelleyBlock protocol (AlonzoEra StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (AlonzoEra StandardCrypto)) -> Maybe LedgerEvent #

ConvertLedgerEvent (ShelleyBlock protocol (BabbageEra StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (BabbageEra StandardCrypto)) -> Maybe LedgerEvent #

ConvertLedgerEvent (ShelleyBlock protocol (ConwayEra StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (ConwayEra StandardCrypto)) -> Maybe LedgerEvent #

ConvertLedgerEvent (ShelleyBlock protocol (MaryEra StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (MaryEra StandardCrypto)) -> Maybe LedgerEvent #

ConvertLedgerEvent (ShelleyBlock protocol (ShelleyEra StandardCrypto)) 
Instance details

Defined in Cardano.Api.LedgerEvents.ConvertLedgerEvent

Methods

toLedgerEvent :: WrapLedgerEvent (ShelleyBlock protocol (ShelleyEra StandardCrypto)) -> Maybe LedgerEvent #

LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto)) => ProtocolClient (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley)

Methods

protocolClientInfo :: ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) -> ProtocolClientInfo (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley)

type ADDRHASH StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type ADDRHASH StandardCrypto = Blake2b_224
type DSIGN StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type DSIGN StandardCrypto = Ed25519DSIGN
type HASH StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type HASH StandardCrypto = Blake2b_256
type KES StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type KES StandardCrypto = Sum6KES Ed25519DSIGN Blake2b_256
type VRF StandardCrypto 
Instance details

Defined in Cardano.Ledger.Crypto

type VRF StandardCrypto = PraosVRF
data ProtocolClientInfoArgs (CardanoBlock StandardCrypto) 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolClientInfoArgs (CardanoBlock StandardCrypto) = ProtocolClientInfoArgsCardano EpochSlots
data ProtocolInfoArgs (CardanoBlock StandardCrypto) 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolInfoArgs (CardanoBlock StandardCrypto) = ProtocolInfoArgsCardano (CardanoProtocolParams StandardCrypto)
data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolClientInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) = ProtocolClientInfoArgsShelley
data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) = ProtocolInfoArgsShelley (ShelleyGenesis StandardCrypto) (ProtocolParamsShelleyBased StandardCrypto) (ProtocolParams (ShelleyBlock (TPraos StandardCrypto) StandardShelley))

type LedgerEra = ShelleyLedgerEra Era Source #

Currently supported ledger era.

ledgerEraVersion :: Version Source #

Associated version for the fixed LedgerEra.

Wrapped Types

type AddressTypeInEra addrType = AddressTypeInEra addrType Era Source #

type ScriptWitness witCtx = ScriptWitness witCtx Era Source #

type Tx = Tx Era Source #

type TxIns buidl = [(TxIn, BuildTxWith buidl (Witness WitCtxTxIn Era))] Source #

type TxMintValue buidl = TxMintValue buidl Era Source #

type TxOut ctx = TxOut ctx Era Source #

type Witness witCtx = Witness witCtx Era Source #

pattern KeyWitness :: KeyWitnessInCtx ctx -> Witness ctx Source #

pattern Tx :: TxBody -> [KeyWitness] -> Tx Source #

pattern TxInsReference :: [TxIn] -> TxInsReference buidl Source #

pattern TxOut :: AddressInEra -> Value -> TxOutDatum ctx -> ReferenceScript -> TxOut ctx Source #

TxOut specialized for Era

pattern ShelleyTxBody :: TxBody LedgerEra -> [Script LedgerEra] -> TxBodyScriptData -> Maybe (AlonzoTxAuxData LedgerEra) -> TxScriptValidity -> TxBody Source #

pattern ShelleyKeyWitness :: WitVKey 'Witness StandardCrypto -> KeyWitness Source #

txIns :: TxBodyContent buidl -> TxIns buidl Source #

UTxO

newtype UTxO' out Source #

Newtype with phantom types mostly required to work around the poor interface of UTXO and provide Monoid and Foldable instances to make utxo manipulation bareable.

Constructors

UTxO (Map TxIn out) 

Instances

Instances details
Foldable UTxO' Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

fold :: Monoid m => UTxO' m -> m Source #

foldMap :: Monoid m => (a -> m) -> UTxO' a -> m Source #

foldMap' :: Monoid m => (a -> m) -> UTxO' a -> m Source #

foldr :: (a -> b -> b) -> b -> UTxO' a -> b Source #

foldr' :: (a -> b -> b) -> b -> UTxO' a -> b Source #

foldl :: (b -> a -> b) -> b -> UTxO' a -> b Source #

foldl' :: (b -> a -> b) -> b -> UTxO' a -> b Source #

foldr1 :: (a -> a -> a) -> UTxO' a -> a Source #

foldl1 :: (a -> a -> a) -> UTxO' a -> a Source #

toList :: UTxO' a -> [a] Source #

null :: UTxO' a -> Bool Source #

length :: UTxO' a -> Int Source #

elem :: Eq a => a -> UTxO' a -> Bool Source #

maximum :: Ord a => UTxO' a -> a Source #

minimum :: Ord a => UTxO' a -> a Source #

sum :: Num a => UTxO' a -> a Source #

product :: Num a => UTxO' a -> a Source #

Traversable UTxO' Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

traverse :: Applicative f => (a -> f b) -> UTxO' a -> f (UTxO' b) Source #

sequenceA :: Applicative f => UTxO' (f a) -> f (UTxO' a) Source #

mapM :: Monad m => (a -> m b) -> UTxO' a -> m (UTxO' b) Source #

sequence :: Monad m => UTxO' (m a) -> m (UTxO' a) Source #

Functor UTxO' Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

fmap :: (a -> b) -> UTxO' a -> UTxO' b Source #

(<$) :: a -> UTxO' b -> UTxO' a Source #

FromJSON out => FromJSON (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

parseJSON :: Value -> Parser (UTxO' out) #

parseJSONList :: Value -> Parser [UTxO' out] #

omittedField :: Maybe (UTxO' out) #

ToJSON out => ToJSON (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

toJSON :: UTxO' out -> Value #

toEncoding :: UTxO' out -> Encoding #

toJSONList :: [UTxO' out] -> Value #

toEncodingList :: [UTxO' out] -> Encoding #

omitField :: UTxO' out -> Bool #

Monoid (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

mempty :: UTxO' out Source #

mappend :: UTxO' out -> UTxO' out -> UTxO' out Source #

mconcat :: [UTxO' out] -> UTxO' out Source #

Semigroup (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

(<>) :: UTxO' out -> UTxO' out -> UTxO' out Source #

sconcat :: NonEmpty (UTxO' out) -> UTxO' out Source #

stimes :: Integral b => b -> UTxO' out -> UTxO' out Source #

Show out => Show (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

showsPrec :: Int -> UTxO' out -> ShowS Source #

show :: UTxO' out -> String Source #

showList :: [UTxO' out] -> ShowS Source #

Eq out => Eq (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

(==) :: UTxO' out -> UTxO' out -> Bool Source #

(/=) :: UTxO' out -> UTxO' out -> Bool Source #

Extras

Re-exports from cardano-api

class Error e where #

Methods

prettyError :: e -> Doc ann #

Instances

Instances details
Error IOException 
Instance details

Defined in Cardano.Api.Error

Methods

prettyError :: IOException -> Doc ann #

Error DRepMetadataValidationError 
Instance details

Defined in Cardano.Api.DRepMetadata

Error InputDecodeError 
Instance details

Defined in Cardano.Api.DeserialiseAnyOf

Error ErrorAsException 
Instance details

Defined in Cardano.Api.Error

Methods

prettyError :: ErrorAsException -> Doc ann #

Error ScriptExecutionError 
Instance details

Defined in Cardano.Api.Fees

Error FoldBlocksError 
Instance details

Defined in Cardano.Api.LedgerState

Methods

prettyError :: FoldBlocksError -> Doc ann #

Error GenesisConfigError 
Instance details

Defined in Cardano.Api.LedgerState

Error InitialLedgerStateError 
Instance details

Defined in Cardano.Api.LedgerState

Error LeadershipError 
Instance details

Defined in Cardano.Api.LedgerState

Methods

prettyError :: LeadershipError -> Doc ann #

Error LedgerStateError 
Instance details

Defined in Cardano.Api.LedgerState

Error OperationalCertIssueError 
Instance details

Defined in Cardano.Api.OperationalCertificate

Error ProtocolParametersConversionError 
Instance details

Defined in Cardano.Api.ProtocolParameters

Error ProtocolParametersError 
Instance details

Defined in Cardano.Api.ProtocolParameters

Error ScriptDataJsonBytesError 
Instance details

Defined in Cardano.Api.ScriptData

Error ScriptDataJsonError 
Instance details

Defined in Cardano.Api.ScriptData

Error ScriptDataJsonSchemaError 
Instance details

Defined in Cardano.Api.ScriptData

Error ScriptDataRangeError 
Instance details

Defined in Cardano.Api.ScriptData

Error Bech32DecodeError 
Instance details

Defined in Cardano.Api.SerialiseBech32

Error JsonDecodeError 
Instance details

Defined in Cardano.Api.SerialiseJSON

Methods

prettyError :: JsonDecodeError -> Doc ann #

Error TextEnvelopeCddlError 
Instance details

Defined in Cardano.Api.SerialiseLedgerCddl

Error RawBytesHexError 
Instance details

Defined in Cardano.Api.SerialiseRaw

Error TextEnvelopeError 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Error StakePoolMetadataValidationError 
Instance details

Defined in Cardano.Api.StakePoolMetadata

Error TxBodyError 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

prettyError :: TxBodyError -> Doc ann #

Error TxMetadataJsonError 
Instance details

Defined in Cardano.Api.TxMetadata

Error TxMetadataJsonSchemaError 
Instance details

Defined in Cardano.Api.TxMetadata

Error TxMetadataRangeError 
Instance details

Defined in Cardano.Api.TxMetadata

Error () 
Instance details

Defined in Cardano.Api.Error

Methods

prettyError :: () -> Doc ann #

Error e => Error (FileError e) 
Instance details

Defined in Cardano.Api.Error

Methods

prettyError :: FileError e -> Doc ann #

Error (TransactionValidityError era) 
Instance details

Defined in Cardano.Api.Fees

Error (TxBodyErrorAutoBalance era) 
Instance details

Defined in Cardano.Api.Fees

data Doc ann #

Instances

Instances details
Functor Doc 
Instance details

Defined in Prettyprinter.Internal

Methods

fmap :: (a -> b) -> Doc a -> Doc b Source #

(<$) :: a -> Doc b -> Doc a Source #

IsString (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Methods

fromString :: String -> Doc ann Source #

Monoid (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Methods

mempty :: Doc ann Source #

mappend :: Doc ann -> Doc ann -> Doc ann Source #

mconcat :: [Doc ann] -> Doc ann Source #

Semigroup (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Methods

(<>) :: Doc ann -> Doc ann -> Doc ann Source #

sconcat :: NonEmpty (Doc ann) -> Doc ann Source #

stimes :: Integral b => b -> Doc ann -> Doc ann Source #

Generic (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Associated Types

type Rep (Doc ann) :: Type -> Type Source #

Methods

from :: Doc ann -> Rep (Doc ann) x Source #

to :: Rep (Doc ann) x -> Doc ann Source #

Show (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

Methods

showsPrec :: Int -> Doc ann -> ShowS Source #

show :: Doc ann -> String Source #

showList :: [Doc ann] -> ShowS Source #

type Rep (Doc ann) 
Instance details

Defined in Prettyprinter.Internal

type Rep (Doc ann) = D1 ('MetaData "Doc" "Prettyprinter.Internal" "prettyprinter-1.7.1-9vCjPlOjwpdGk0GEh9x7Ph" 'False) (((C1 ('MetaCons "Fail" 'PrefixI 'False) (U1 :: Type -> Type) :+: (C1 ('MetaCons "Empty" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Char" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Char)))) :+: (C1 ('MetaCons "Text" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "Line" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "FlatAlt" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)))))) :+: ((C1 ('MetaCons "Cat" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))) :+: (C1 ('MetaCons "Nest" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Int) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))) :+: C1 ('MetaCons "Union" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann))))) :+: ((C1 ('MetaCons "Column" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int -> Doc ann))) :+: C1 ('MetaCons "WithPageWidth" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PageWidth -> Doc ann)))) :+: (C1 ('MetaCons "Nesting" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Int -> Doc ann))) :+: C1 ('MetaCons "Annotated" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ann) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Doc ann)))))))

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

Defined in Cardano.Api.Eras.Core

Methods

pretty :: AnyCardanoEra -> Doc ann #

prettyList :: [AnyCardanoEra] -> Doc ann #

Pretty TxOutInAnyEra 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

pretty :: TxOutInAnyEra -> Doc ann #

prettyList :: [TxOutInAnyEra] -> Doc ann #

Pretty TxIn 
Instance details

Defined in Cardano.Api.TxIn

Methods

pretty :: TxIn -> Doc ann #

prettyList :: [TxIn] -> Doc ann #

Pretty Data 
Instance details

Defined in PlutusCore.Data

Methods

pretty :: Data -> Doc ann #

prettyList :: [Data] -> 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

Methods

pretty :: ParserErrorBundle -> Doc ann #

prettyList :: [ParserErrorBundle] -> Doc ann #

Pretty CostModelApplyError 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Methods

pretty :: CostModelApplyError -> Doc ann #

prettyList :: [CostModelApplyError] -> Doc ann #

Pretty CostModelApplyWarn 
Instance details

Defined in PlutusCore.Evaluation.Machine.CostModelInterface

Methods

pretty :: CostModelApplyWarn -> Doc ann #

prettyList :: [CostModelApplyWarn] -> Doc ann #

Pretty Address 
Instance details

Defined in PlutusLedgerApi.V1.Address

Methods

pretty :: Address -> Doc ann #

prettyList :: [Address] -> 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

Methods

pretty :: StakingCredential -> Doc ann #

prettyList :: [StakingCredential] -> Doc ann #

Pretty PubKeyHash 
Instance details

Defined in PlutusLedgerApi.V1.Crypto

Methods

pretty :: PubKeyHash -> Doc ann #

prettyList :: [PubKeyHash] -> 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 
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 
Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: RedeemerHash -> Doc ann #

prettyList :: [RedeemerHash] -> Doc ann #

Pretty ScriptHash 
Instance details

Defined in PlutusLedgerApi.V1.Scripts

Methods

pretty :: ScriptHash -> Doc ann #

prettyList :: [ScriptHash] -> Doc ann #

Pretty TxId 
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 
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 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 BuiltinBLS12_381_G1_Element 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinBLS12_381_G1_Element -> Doc ann #

prettyList :: [BuiltinBLS12_381_G1_Element] -> Doc ann #

Pretty BuiltinBLS12_381_G2_Element 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinBLS12_381_G2_Element -> Doc ann #

prettyList :: [BuiltinBLS12_381_G2_Element] -> Doc ann #

Pretty BuiltinBLS12_381_MlResult 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinBLS12_381_MlResult -> Doc ann #

prettyList :: [BuiltinBLS12_381_MlResult] -> Doc ann #

Pretty BuiltinByteString 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinByteString -> Doc ann #

prettyList :: [BuiltinByteString] -> Doc ann #

Pretty BuiltinData 
Instance details

Defined in PlutusTx.Builtins.Internal

Methods

pretty :: BuiltinData -> Doc ann #

prettyList :: [BuiltinData] -> 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) 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Methods

pretty :: ShelleyBasedEra era -> Doc ann #

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

Pretty (CardanoEra era) 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

pretty :: CardanoEra era -> Doc ann #

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

Show a => Pretty (ShowOf a) 
Instance details

Defined in Cardano.Api.Via.ShowOf

Methods

pretty :: ShowOf a -> Doc ann #

prettyList :: [ShowOf 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 #

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 #

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

(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 (Eq (VerificationKey keyrole), Show (VerificationKey keyrole), SerialiseAsRawBytes (Hash keyrole), HasTextEnvelope (VerificationKey keyrole), HasTextEnvelope (SigningKey keyrole)) => Key keyrole where #

Associated Types

data VerificationKey keyrole #

data SigningKey keyrole #

Instances

Instances details
Key ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

Associated Types

data VerificationKey ByronKey #

data SigningKey ByronKey #

Key ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

Key KesKey 
Instance details

Defined in Cardano.Api.Keys.Praos

Associated Types

data VerificationKey KesKey #

data SigningKey KesKey #

Key VrfKey 
Instance details

Defined in Cardano.Api.Keys.Praos

Associated Types

data VerificationKey VrfKey #

data SigningKey VrfKey #

Key CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data VerificationKey DRepKey #

data SigningKey DRepKey #

Key GenesisDelegateExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key GenesisExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key GenesisUTxOKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key StakeExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Key StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data VerificationKey StakeKey #

data SigningKey StakeKey #

Key StakePoolKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data Block era where #

Constructors

ByronBlock :: ByronBlock -> Block ByronEra 
ShelleyBlock :: forall era. ShelleyBasedEra era -> ShelleyBlock (ConsensusProtocol era) (ShelleyLedgerEra era) -> Block era 

Instances

Instances details
Show (Block era) 
Instance details

Defined in Cardano.Api.Block

Methods

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

show :: Block era -> String Source #

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

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 #

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

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

Defined in Control.Monad.Trans.Reader

Methods

liftIO :: IO a -> ReaderT r 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 (ContT r m) 
Instance details

Defined in Control.Monad.Trans.Cont

Methods

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

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

Defined in Cardano.Api.IPC.Monad

Methods

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

newtype File content (direction :: FileDirection) #

Constructors

File 

Fields

Instances

Instances details
FromJSON (File content direction) 
Instance details

Defined in Cardano.Api.IO.Base

Methods

parseJSON :: Value -> Parser (File content direction) #

parseJSONList :: Value -> Parser [File content direction] #

omittedField :: Maybe (File content direction) #

ToJSON (File content direction) 
Instance details

Defined in Cardano.Api.IO.Base

Methods

toJSON :: File content direction -> Value #

toEncoding :: File content direction -> Encoding #

toJSONList :: [File content direction] -> Value #

toEncodingList :: [File content direction] -> Encoding #

omitField :: File content direction -> Bool #

IsString (File content direction) 
Instance details

Defined in Cardano.Api.IO.Base

Methods

fromString :: String -> File content direction Source #

Read (File content direction) 
Instance details

Defined in Cardano.Api.IO.Base

Methods

readsPrec :: Int -> ReadS (File content direction) Source #

readList :: ReadS [File content direction] Source #

readPrec :: ReadPrec (File content direction) Source #

readListPrec :: ReadPrec [File content direction] Source #

Show (File content direction) 
Instance details

Defined in Cardano.Api.IO.Base

Methods

showsPrec :: Int -> File content direction -> ShowS Source #

show :: File content direction -> String Source #

showList :: [File content direction] -> ShowS Source #

Eq (File content direction) 
Instance details

Defined in Cardano.Api.IO.Base

Methods

(==) :: File content direction -> File content direction -> Bool Source #

(/=) :: File content direction -> File content direction -> Bool Source #

Ord (File content direction) 
Instance details

Defined in Cardano.Api.IO.Base

Methods

compare :: File content direction -> File content direction -> Ordering Source #

(<) :: File content direction -> File content direction -> Bool Source #

(<=) :: File content direction -> File content direction -> Bool Source #

(>) :: File content direction -> File content direction -> Bool Source #

(>=) :: File content direction -> File content direction -> Bool Source #

max :: File content direction -> File content direction -> File content direction Source #

min :: File content direction -> File content direction -> File content direction Source #

newtype ExceptT e (m :: Type -> Type) a Source #

A monad transformer that adds exceptions to other monads.

ExceptT constructs a monad parameterized over two things:

  • e - The exception type.
  • m - The inner monad.

The return function yields a computation that produces the given value, while >>= sequences two subcomputations, exiting on the first exception.

Constructors

ExceptT (m (Either e a)) 

Instances

Instances details
FunctorT (ExceptT e :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Barbies.Internal.FunctorT

Methods

tmap :: forall f g (x :: k'). (forall (a :: k). f a -> g a) -> ExceptT e f x -> ExceptT e g x

TraversableT (ExceptT e :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Barbies.Internal.TraversableT

Methods

ttraverse :: forall e0 f g (x :: k'). Applicative e0 => (forall (a :: k). f a -> e0 (g a)) -> ExceptT e f x -> e0 (ExceptT e g x)

DistributiveT (ExceptT e :: (Type -> Type) -> Type -> Type) 
Instance details

Defined in Barbies.Internal.DistributiveT

Methods

tdistribute :: forall f (g :: Type -> Type) (x :: i). Functor f => f (ExceptT e g x) -> ExceptT e (Compose f g) x

Functor m => Generic1 (ExceptT e m :: Type -> Type) 
Instance details

Defined in Control.Monad.Trans.Except

Associated Types

type Rep1 (ExceptT e m) :: k -> Type Source #

Methods

from1 :: forall (a :: k). ExceptT e m a -> Rep1 (ExceptT e m) a Source #

to1 :: forall (a :: k). Rep1 (ExceptT e m) a -> ExceptT e m a Source #

Monad m => MonadError e (ExceptT e m)

Since: mtl-2.2

Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> ExceptT e m a Source #

catchError :: ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e 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 #

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

Defined in Control.Monad.Trans.Except

Methods

fail :: String -> ExceptT e m a Source #

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

Defined in Control.Monad.Trans.Except

Methods

mfix :: (a -> ExceptT e m a) -> ExceptT e 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 #

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

Defined in Control.Monad.Trans.Except

Methods

mzip :: ExceptT e m a -> ExceptT e m b -> ExceptT e m (a, b) Source #

mzipWith :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c Source #

munzip :: ExceptT e m (a, b) -> (ExceptT e m a, ExceptT e m b) Source #

Foldable f => Foldable (ExceptT e f) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

fold :: Monoid m => ExceptT e f m -> m Source #

foldMap :: Monoid m => (a -> m) -> ExceptT e f a -> m Source #

foldMap' :: Monoid m => (a -> m) -> ExceptT e f a -> m Source #

foldr :: (a -> b -> b) -> b -> ExceptT e f a -> b Source #

foldr' :: (a -> b -> b) -> b -> ExceptT e f a -> b Source #

foldl :: (b -> a -> b) -> b -> ExceptT e f a -> b Source #

foldl' :: (b -> a -> b) -> b -> ExceptT e f a -> b Source #

foldr1 :: (a -> a -> a) -> ExceptT e f a -> a Source #

foldl1 :: (a -> a -> a) -> ExceptT e f a -> a Source #

toList :: ExceptT e f a -> [a] Source #

null :: ExceptT e f a -> Bool Source #

length :: ExceptT e f a -> Int Source #

elem :: Eq a => a -> ExceptT e f a -> Bool Source #

maximum :: Ord a => ExceptT e f a -> a Source #

minimum :: Ord a => ExceptT e f a -> a Source #

sum :: Num a => ExceptT e f a -> a Source #

product :: Num a => ExceptT e f a -> a Source #

(Eq e, Eq1 m) => Eq1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftEq :: (a -> b -> Bool) -> ExceptT e m a -> ExceptT e m b -> Bool Source #

(Ord e, Ord1 m) => Ord1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftCompare :: (a -> b -> Ordering) -> ExceptT e m a -> ExceptT e m b -> Ordering Source #

(Read e, Read1 m) => Read1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (ExceptT e m a) Source #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [ExceptT e m a] Source #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (ExceptT e m a) Source #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [ExceptT e m a] Source #

(Show e, Show1 m) => Show1 (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> ExceptT e m a -> ShowS Source #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [ExceptT e m a] -> ShowS Source #

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

Defined in Control.Monad.Trans.Except

Methods

contramap :: (a' -> a) -> ExceptT e m a -> ExceptT e m a' Source #

(>$) :: b -> ExceptT e m b -> ExceptT e m a Source #

Traversable f => Traversable (ExceptT e f) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

traverse :: Applicative f0 => (a -> f0 b) -> ExceptT e f a -> f0 (ExceptT e f b) Source #

sequenceA :: Applicative f0 => ExceptT e f (f0 a) -> f0 (ExceptT e f a) Source #

mapM :: Monad m => (a -> m b) -> ExceptT e f a -> m (ExceptT e f b) Source #

sequence :: Monad m => ExceptT e f (m a) -> m (ExceptT e f a) Source #

(Functor m, Monad m, Monoid e) => Alternative (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

empty :: ExceptT e m a Source #

(<|>) :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a Source #

some :: ExceptT e m a -> ExceptT e m [a] Source #

many :: ExceptT e m a -> ExceptT e m [a] Source #

(Functor m, Monad m) => Applicative (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

pure :: a -> ExceptT e m a Source #

(<*>) :: ExceptT e m (a -> b) -> ExceptT e m a -> ExceptT e m b Source #

liftA2 :: (a -> b -> c) -> ExceptT e m a -> ExceptT e m b -> ExceptT e m c Source #

(*>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b Source #

(<*) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m a Source #

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

Defined in Control.Monad.Trans.Except

Methods

fmap :: (a -> b) -> ExceptT e m a -> ExceptT e m b Source #

(<$) :: a -> ExceptT e m b -> ExceptT e m a Source #

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

Defined in Control.Monad.Trans.Except

Methods

(>>=) :: ExceptT e m a -> (a -> ExceptT e m b) -> ExceptT e m b Source #

(>>) :: ExceptT e m a -> ExceptT e m b -> ExceptT e m b Source #

return :: a -> ExceptT e m a Source #

(Monad m, Monoid e) => MonadPlus (ExceptT e m) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

mzero :: ExceptT e m a Source #

mplus :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a Source #

MonadCatch m => MonadCatch (ExceptT e m)

Catches exceptions from the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

catch :: (HasCallStack, Exception e0) => ExceptT e m a -> (e0 -> ExceptT e m a) -> ExceptT e m a Source #

MonadMask m => MonadMask (ExceptT e m)

Since: exceptions-0.9.0

Instance details

Defined in Control.Monad.Catch

Methods

mask :: HasCallStack => ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b Source #

uninterruptibleMask :: HasCallStack => ((forall a. ExceptT e m a -> ExceptT e m a) -> ExceptT e m b) -> ExceptT e m b Source #

generalBracket :: HasCallStack => ExceptT e m a -> (a -> ExitCase b -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m (b, c) Source #

MonadThrow m => MonadThrow (ExceptT e m)

Throws exceptions into the base monad.

Instance details

Defined in Control.Monad.Catch

Methods

throwM :: (HasCallStack, Exception e0) => e0 -> ExceptT e m a Source #

Generic (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Associated Types

type Rep (ExceptT e m a) :: Type -> Type Source #

Methods

from :: ExceptT e m a -> Rep (ExceptT e m a) x Source #

to :: Rep (ExceptT e m a) x -> ExceptT e m a Source #

(Read e, Read1 m, Read a) => Read (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

(Show e, Show1 m, Show a) => Show (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

showsPrec :: Int -> ExceptT e m a -> ShowS Source #

show :: ExceptT e m a -> String Source #

showList :: [ExceptT e m a] -> ShowS Source #

(Eq e, Eq1 m, Eq a) => Eq (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

(==) :: ExceptT e m a -> ExceptT e m a -> Bool Source #

(/=) :: ExceptT e m a -> ExceptT e m a -> Bool Source #

(Ord e, Ord1 m, Ord a) => Ord (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

Methods

compare :: ExceptT e m a -> ExceptT e m a -> Ordering Source #

(<) :: ExceptT e m a -> ExceptT e m a -> Bool Source #

(<=) :: ExceptT e m a -> ExceptT e m a -> Bool Source #

(>) :: ExceptT e m a -> ExceptT e m a -> Bool Source #

(>=) :: ExceptT e m a -> ExceptT e m a -> Bool Source #

max :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a Source #

min :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a Source #

type Rep1 (ExceptT e m :: Type -> Type) 
Instance details

Defined in Control.Monad.Trans.Except

type Rep1 (ExceptT e m :: Type -> Type) = D1 ('MetaData "ExceptT" "Control.Monad.Trans.Except" "transformers-0.6.1.0" 'True) (C1 ('MetaCons "ExceptT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (m :.: Rec1 (Either e))))
type STM (ExceptT e m) 
Instance details

Defined in Control.Monad.Class.MonadSTM.Trans

type STM (ExceptT e m) = ExceptT e (STM m)
type TArray (ExceptT e m) 
Instance details

Defined in Control.Monad.Class.MonadSTM.Trans

type TArray (ExceptT e m) = TArray m
type TBQueue (ExceptT e m) 
Instance details

Defined in Control.Monad.Class.MonadSTM.Trans

type TBQueue (ExceptT e m) = TBQueue m
type TChan (ExceptT e m) 
Instance details

Defined in Control.Monad.Class.MonadSTM.Trans

type TChan (ExceptT e m) = TChan m
type TMVar (ExceptT e m) 
Instance details

Defined in Control.Monad.Class.MonadSTM.Trans

type TMVar (ExceptT e m) = TMVar m
type TQueue (ExceptT e m) 
Instance details

Defined in Control.Monad.Class.MonadSTM.Trans

type TQueue (ExceptT e m) = TQueue m
type TSem (ExceptT e m) 
Instance details

Defined in Control.Monad.Class.MonadSTM.Trans

type TSem (ExceptT e m) = TSem m
type TVar (ExceptT e m) 
Instance details

Defined in Control.Monad.Class.MonadSTM.Trans

type TVar (ExceptT e m) = TVar m
type Rep (ExceptT e m a) 
Instance details

Defined in Control.Monad.Trans.Except

type Rep (ExceptT e m a) = D1 ('MetaData "ExceptT" "Control.Monad.Trans.Except" "transformers-0.6.1.0" 'True) (C1 ('MetaCons "ExceptT" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (m (Either e a)))))

data Env #

Constructors

Env 

Fields

data family Hash keyrole #

Instances

Instances details
FromJSON (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

Methods

parseJSON :: Value -> Parser (Hash BlockHeader) #

parseJSONList :: Value -> Parser [Hash BlockHeader] #

omittedField :: Maybe (Hash BlockHeader) #

FromJSON (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

parseJSON :: Value -> Parser (Hash DRepKey) #

parseJSONList :: Value -> Parser [Hash DRepKey] #

omittedField :: Maybe (Hash DRepKey) #

FromJSON (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

parseJSON :: Value -> Parser (Hash GenesisKey) #

parseJSONList :: Value -> Parser [Hash GenesisKey] #

omittedField :: Maybe (Hash GenesisKey) #

FromJSON (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

parseJSON :: Value -> Parser (Hash PaymentKey) #

parseJSONList :: Value -> Parser [Hash PaymentKey] #

omittedField :: Maybe (Hash PaymentKey) #

FromJSON (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

parseJSON :: Value -> Parser (Hash StakePoolKey) #

parseJSONList :: Value -> Parser [Hash StakePoolKey] #

omittedField :: Maybe (Hash StakePoolKey) #

FromJSON (Hash ScriptData) 
Instance details

Defined in Cardano.Api.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.ScriptData

Methods

fromJSONKey :: FromJSONKeyFunction (Hash ScriptData)

fromJSONKeyList :: FromJSONKeyFunction [Hash ScriptData]

ToJSON (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

ToJSON (Hash DRepKey) 
Instance details

Defined in Cardano.Api.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) 
Instance details

Defined in Cardano.Api.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) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toJSON :: Hash PaymentKey -> Value #

toEncoding :: Hash PaymentKey -> Encoding #

toJSONList :: [Hash PaymentKey] -> Value #

toEncodingList :: [Hash PaymentKey] -> Encoding #

omitField :: Hash PaymentKey -> Bool #

ToJSON (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToJSON (Hash ScriptData) 
Instance details

Defined in Cardano.Api.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.Keys.Shelley

Methods

toJSONKey :: ToJSONKeyFunction (Hash DRepKey)

toJSONKeyList :: ToJSONKeyFunction [Hash DRepKey]

ToJSONKey (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toJSONKey :: ToJSONKeyFunction (Hash GenesisKey)

toJSONKeyList :: ToJSONKeyFunction [Hash GenesisKey]

ToJSONKey (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toJSONKey :: ToJSONKeyFunction (Hash PaymentKey)

toJSONKeyList :: ToJSONKeyFunction [Hash PaymentKey]

ToJSONKey (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toJSONKey :: ToJSONKeyFunction (Hash StakePoolKey)

toJSONKeyList :: ToJSONKeyFunction [Hash StakePoolKey]

ToJSONKey (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

Methods

toJSONKey :: ToJSONKeyFunction (Hash ScriptData)

toJSONKeyList :: ToJSONKeyFunction [Hash ScriptData]

IsString (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

IsString (Hash GovernancePoll) 
Instance details

Defined in Cardano.Api.Governance.Poll

IsString (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

IsString (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

IsString (Hash KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

IsString (Hash VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

IsString (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

Show (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

Show (Hash DRepMetadata) 
Instance details

Defined in Cardano.Api.DRepMetadata

Show (Hash GovernancePoll) 
Instance details

Defined in Cardano.Api.Governance.Poll

Show (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Show (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Show (Hash KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Show (Hash VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Show (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

Show (Hash StakePoolMetadata) 
Instance details

Defined in Cardano.Api.StakePoolMetadata

HasTypeProxy a => HasTypeProxy (Hash a) 
Instance details

Defined in Cardano.Api.Hash

Associated Types

data AsType (Hash a) #

Methods

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

SerialiseAsBech32 (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (Hash KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsCBOR (Hash VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsCBOR (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

SerialiseAsRawBytes (Hash DRepMetadata) 
Instance details

Defined in Cardano.Api.DRepMetadata

SerialiseAsRawBytes (Hash GovernancePoll) 
Instance details

Defined in Cardano.Api.Governance.Poll

SerialiseAsRawBytes (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (Hash KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsRawBytes (Hash VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsRawBytes (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

SerialiseAsRawBytes (Hash StakePoolMetadata) 
Instance details

Defined in Cardano.Api.StakePoolMetadata

FromCBOR (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

fromCBOR :: Decoder s (Hash ByronKey)

label :: Proxy (Hash ByronKey) -> Text

FromCBOR (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (Hash KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

fromCBOR :: Decoder s (Hash KesKey)

label :: Proxy (Hash KesKey) -> Text

FromCBOR (Hash VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

fromCBOR :: Decoder s (Hash VrfKey)

label :: Proxy (Hash VrfKey) -> Text

FromCBOR (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash DRepKey)

label :: Proxy (Hash DRepKey) -> Text

FromCBOR (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash GenesisKey)

label :: Proxy (Hash GenesisKey) -> Text

FromCBOR (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash PaymentKey)

label :: Proxy (Hash PaymentKey) -> Text

FromCBOR (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash StakeKey)

label :: Proxy (Hash StakeKey) -> Text

FromCBOR (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash StakePoolKey)

label :: Proxy (Hash StakePoolKey) -> Text

ToCBOR (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: Hash ByronKey -> Encoding

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

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

ToCBOR (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: Hash ByronKeyLegacy -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash ByronKeyLegacy) -> Size

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

ToCBOR (Hash KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

toCBOR :: Hash KesKey -> Encoding

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

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

ToCBOR (Hash VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

toCBOR :: Hash VrfKey -> Encoding

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

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

ToCBOR (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash CommitteeColdExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeColdExtendedKey) -> Size

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

ToCBOR (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash CommitteeColdKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeColdKey) -> Size

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

ToCBOR (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash CommitteeHotExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeHotExtendedKey) -> Size

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

ToCBOR (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash CommitteeHotKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeHotKey) -> Size

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

ToCBOR (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash DRepExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash DRepExtendedKey) -> Size

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

ToCBOR (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash DRepKey -> Encoding

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

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

ToCBOR (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisDelegateExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisDelegateExtendedKey) -> Size

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

ToCBOR (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisDelegateKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisDelegateKey) -> Size

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

ToCBOR (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisExtendedKey) -> Size

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

ToCBOR (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisKey) -> Size

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

ToCBOR (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisUTxOKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisUTxOKey) -> Size

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

ToCBOR (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash PaymentExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash PaymentExtendedKey) -> Size

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

ToCBOR (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash PaymentKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash PaymentKey) -> Size

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

ToCBOR (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash StakeExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash StakeExtendedKey) -> Size

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

ToCBOR (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash StakeKey -> Encoding

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

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

ToCBOR (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash StakePoolKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash StakePoolKey) -> Size

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

Eq (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

Eq (Hash DRepMetadata) 
Instance details

Defined in Cardano.Api.DRepMetadata

Eq (Hash GovernancePoll) 
Instance details

Defined in Cardano.Api.Governance.Poll

Eq (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Eq (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Eq (Hash KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Eq (Hash VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Eq (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

Eq (Hash StakePoolMetadata) 
Instance details

Defined in Cardano.Api.StakePoolMetadata

Ord (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

Ord (Hash GovernancePoll) 
Instance details

Defined in Cardano.Api.Governance.Poll

Ord (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Ord (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Ord (Hash KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Ord (Hash VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Ord (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

newtype Hash BlockHeader 
Instance details

Defined in Cardano.Api.Block

newtype Hash DRepMetadata 
Instance details

Defined in Cardano.Api.DRepMetadata

newtype Hash GovernancePoll 
Instance details

Defined in Cardano.Api.Governance.Poll

newtype Hash ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

newtype Hash ByronKey = ByronKeyHash KeyHash
newtype Hash ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

newtype Hash KesKey 
Instance details

Defined in Cardano.Api.Keys.Praos

newtype Hash KesKey = KesKeyHash (Hash StandardCrypto (VerKeyKES StandardCrypto))
newtype Hash VrfKey 
Instance details

Defined in Cardano.Api.Keys.Praos

newtype Hash VrfKey = VrfKeyHash (Hash StandardCrypto (VerKeyVRF StandardCrypto))
newtype Hash CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash DRepKey = DRepKeyHash {}
newtype Hash GenesisDelegateExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash GenesisExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash GenesisUTxOKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash StakeExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash StakeKey = StakeKeyHash {}
newtype Hash StakePoolKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

newtype Hash StakePoolMetadata 
Instance details

Defined in Cardano.Api.StakePoolMetadata

data AsType (Hash a) 
Instance details

Defined in Cardano.Api.Hash

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

type Except e = ExceptT e Identity Source #

The parameterizable exception monad.

Computations are either exceptions or normal values.

The return function returns a normal value, while >>= exits on the first exception. For a variant that continues after an error and collects all the errors, see Errors.

class Monad m => MonadError e (m :: Type -> Type) | m -> e where Source #

The strategy of combining computations that can throw exceptions by bypassing bound functions from the point an exception is thrown to the point that it is handled.

Is parameterized over the type of error information and the monad type constructor. It is common to use Either String as the monad type constructor for an error monad in which error descriptions take the form of strings. In that case and many other common cases the resulting monad is already defined as an instance of the MonadError class. You can also define your own error type and/or use a monad type constructor other than Either String or Either IOError. In these cases you will have to explicitly define instances of the MonadError class. (If you are using the deprecated Control.Monad.Error or Control.Monad.Trans.Error, you may also have to define an Error instance.)

Methods

throwError :: e -> m a Source #

Is used within a monadic computation to begin exception processing.

catchError :: m a -> (e -> m a) -> m a Source #

A handler function to handle previous errors and return to normal execution. A common idiom is:

do { action1; action2; action3 } `catchError` handler

where the action functions can call throwError. Note that handler and the do-block must have the same return type.

Instances

Instances details
MonadError IOException IO 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: IOException -> IO a Source #

catchError :: IO a -> (IOException -> IO a) -> IO a Source #

MonadError () Maybe

Since: mtl-2.2.2

Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: () -> Maybe a Source #

catchError :: Maybe a -> (() -> Maybe a) -> Maybe a Source #

MonadError e (Either e) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> Either e a Source #

catchError :: Either e a -> (e -> Either e a) -> Either e a Source #

MonadError e m => MonadError e (Free m) 
Instance details

Defined in Control.Monad.Free

Methods

throwError :: e -> Free m a Source #

catchError :: Free m a -> (e -> Free m a) -> Free m a Source #

MonadError e m => MonadError e (MaybeT m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> MaybeT m a Source #

catchError :: MaybeT m a -> (e -> MaybeT m a) -> MaybeT m a Source #

(Functor f, MonadError e m) => MonadError e (FreeT f m) 
Instance details

Defined in Control.Monad.Trans.Free

Methods

throwError :: e -> FreeT f m a Source #

catchError :: FreeT f m a -> (e -> FreeT f m a) -> FreeT f m a Source #

(Monoid w, MonadError e m) => MonadError e (AccumT w m)

Since: mtl-2.3

Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> AccumT w m a Source #

catchError :: AccumT w m a -> (e -> AccumT w m a) -> AccumT w m a Source #

Monad m => MonadError e (ExceptT e m)

Since: mtl-2.2

Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> ExceptT e m a Source #

catchError :: ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a Source #

MonadError e m => MonadError e (IdentityT m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> IdentityT m a Source #

catchError :: IdentityT m a -> (e -> IdentityT m a) -> IdentityT m a Source #

MonadError e m => MonadError e (ReaderT r m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> ReaderT r m a Source #

catchError :: ReaderT r m a -> (e -> ReaderT r m a) -> ReaderT r m a Source #

MonadError e m => MonadError e (StateT s m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> StateT s m a Source #

catchError :: StateT s m a -> (e -> StateT s m a) -> StateT s m a Source #

MonadError e m => MonadError e (StateT s m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> StateT s m a Source #

catchError :: StateT s m a -> (e -> StateT s m a) -> StateT s m a Source #

(Monoid w, MonadError e m) => MonadError e (WriterT w m)

Since: mtl-2.3

Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> WriterT w m a Source #

catchError :: WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a Source #

(Monoid w, MonadError e m) => MonadError e (WriterT w m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> WriterT w m a Source #

catchError :: WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a Source #

(Monoid w, MonadError e m) => MonadError e (WriterT w m) 
Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> WriterT w m a Source #

catchError :: WriterT w m a -> (e -> WriterT w m a) -> WriterT w m a Source #

(Monoid w, MonadError e m) => MonadError e (RWST r w s m)

Since: mtl-2.3

Instance details

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> RWST r w s m a Source #

catchError :: RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a Source #

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

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> RWST r w s m a Source #

catchError :: RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s m a Source #

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

Defined in Control.Monad.Error.Class

Methods

throwError :: e -> RWST r w s m a Source #

catchError :: RWST r w s m a -> (e -> RWST r w s m a) -> RWST r w s 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 #

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

Defined in Control.Monad.Trans.Except

Methods

lift :: Monad m => m a -> ExceptT e 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 (StateT s) 
Instance details

Defined in Control.Monad.Trans.State.Strict

Methods

lift :: Monad m => m a -> StateT s 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 #

data Address addrtype where #

Constructors

ByronAddress :: Address -> Address ByronAddr 
ShelleyAddress :: Network -> PaymentCredential StandardCrypto -> StakeReference StandardCrypto -> Address ShelleyAddr 

Instances

Instances details
Arbitrary (Address ByronAddr) Source # 
Instance details

Defined in Hydra.Cardano.Api.Address

FromJSON (Address ByronAddr) 
Instance details

Defined in Cardano.Api.Address

Methods

parseJSON :: Value -> Parser (Address ByronAddr) #

parseJSONList :: Value -> Parser [Address ByronAddr] #

omittedField :: Maybe (Address ByronAddr) #

FromJSON (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

Methods

parseJSON :: Value -> Parser (Address ShelleyAddr) #

parseJSONList :: Value -> Parser [Address ShelleyAddr] #

omittedField :: Maybe (Address ShelleyAddr) #

ToJSON (Address ByronAddr) 
Instance details

Defined in Cardano.Api.Address

ToJSON (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

Show (Address addrtype) 
Instance details

Defined in Cardano.Api.Address

Methods

showsPrec :: Int -> Address addrtype -> ShowS Source #

show :: Address addrtype -> String Source #

showList :: [Address addrtype] -> ShowS Source #

SerialiseAddress (Address ByronAddr) 
Instance details

Defined in Cardano.Api.Address

SerialiseAddress (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

HasTypeProxy addrtype => HasTypeProxy (Address addrtype) 
Instance details

Defined in Cardano.Api.Address

Associated Types

data AsType (Address addrtype) #

Methods

proxyToAsType :: Proxy (Address addrtype) -> AsType (Address addrtype) #

SerialiseAsBech32 (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

SerialiseAsRawBytes (Address ByronAddr) 
Instance details

Defined in Cardano.Api.Address

SerialiseAsRawBytes (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

NFData (Address addrtype) 
Instance details

Defined in Cardano.Api.Address

Methods

rnf :: Address addrtype -> () Source #

Eq (Address addrtype) 
Instance details

Defined in Cardano.Api.Address

Methods

(==) :: Address addrtype -> Address addrtype -> Bool Source #

(/=) :: Address addrtype -> Address addrtype -> Bool Source #

Ord (Address addrtype) 
Instance details

Defined in Cardano.Api.Address

Methods

compare :: Address addrtype -> Address addrtype -> Ordering Source #

(<) :: Address addrtype -> Address addrtype -> Bool Source #

(<=) :: Address addrtype -> Address addrtype -> Bool Source #

(>) :: Address addrtype -> Address addrtype -> Bool Source #

(>=) :: Address addrtype -> Address addrtype -> Bool Source #

max :: Address addrtype -> Address addrtype -> Address addrtype Source #

min :: Address addrtype -> Address addrtype -> Address addrtype Source #

data AsType (Address addrtype) 
Instance details

Defined in Cardano.Api.Address

data AsType (Address addrtype) = AsAddress (AsType addrtype)

data ProtocolParameters #

Instances

Instances details
FromJSON ProtocolParameters 
Instance details

Defined in Cardano.Api.ProtocolParameters

ToJSON ProtocolParameters 
Instance details

Defined in Cardano.Api.ProtocolParameters

Generic ProtocolParameters 
Instance details

Defined in Cardano.Api.ProtocolParameters

Associated Types

type Rep ProtocolParameters :: Type -> Type Source #

Show ProtocolParameters 
Instance details

Defined in Cardano.Api.ProtocolParameters

Eq ProtocolParameters 
Instance details

Defined in Cardano.Api.ProtocolParameters

type Rep ProtocolParameters 
Instance details

Defined in Cardano.Api.ProtocolParameters

type Rep ProtocolParameters = D1 ('MetaData "ProtocolParameters" "Cardano.Api.ProtocolParameters" "cardano-api-8.42.0.0-dXRaVskXAtCMoDkAxRwdo-internal" 'False) (C1 ('MetaCons "ProtocolParameters" 'PrefixI 'True) ((((S1 ('MetaSel ('Just "protocolParamProtocolVersion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Natural, Natural)) :*: (S1 ('MetaSel ('Just "protocolParamDecentralization") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Rational)) :*: S1 ('MetaSel ('Just "protocolParamExtraPraosEntropy") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PraosNonce)))) :*: (S1 ('MetaSel ('Just "protocolParamMaxBlockHeaderSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: (S1 ('MetaSel ('Just "protocolParamMaxBlockBodySize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Just "protocolParamMaxTxSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural)))) :*: ((S1 ('MetaSel ('Just "protocolParamTxFeeFixed") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin) :*: (S1 ('MetaSel ('Just "protocolParamTxFeePerByte") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin) :*: S1 ('MetaSel ('Just "protocolParamMinUTxOValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Coin)))) :*: (S1 ('MetaSel ('Just "protocolParamStakeAddressDeposit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin) :*: (S1 ('MetaSel ('Just "protocolParamStakePoolDeposit") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin) :*: S1 ('MetaSel ('Just "protocolParamMinPoolCost") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin))))) :*: (((S1 ('MetaSel ('Just "protocolParamPoolRetireMaxEpoch") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochInterval) :*: (S1 ('MetaSel ('Just "protocolParamStakePoolTargetNum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Natural) :*: S1 ('MetaSel ('Just "protocolParamPoolPledgeInfluence") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational))) :*: (S1 ('MetaSel ('Just "protocolParamMonetaryExpansion") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational) :*: (S1 ('MetaSel ('Just "protocolParamTreasuryCut") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Rational) :*: S1 ('MetaSel ('Just "protocolParamCostModels") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map AnyPlutusScriptVersion CostModel))))) :*: ((S1 ('MetaSel ('Just "protocolParamPrices") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExecutionUnitPrices)) :*: (S1 ('MetaSel ('Just "protocolParamMaxTxExUnits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExecutionUnits)) :*: S1 ('MetaSel ('Just "protocolParamMaxBlockExUnits") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ExecutionUnits)))) :*: ((S1 ('MetaSel ('Just "protocolParamMaxValueSize") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)) :*: S1 ('MetaSel ('Just "protocolParamCollateralPercent") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural))) :*: (S1 ('MetaSel ('Just "protocolParamMaxCollateralInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural)) :*: S1 ('MetaSel ('Just "protocolParamUTxOCostPerByte") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Coin))))))))

data ShelleyGenesis c #

Constructors

ShelleyGenesis 

Fields

Instances

Instances details
Crypto c => FromJSON (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

parseJSON :: Value -> Parser (ShelleyGenesis c) #

parseJSONList :: Value -> Parser [ShelleyGenesis c] #

omittedField :: Maybe (ShelleyGenesis c) #

Crypto c => ToJSON (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toJSON :: ShelleyGenesis c -> Value #

toEncoding :: ShelleyGenesis c -> Encoding #

toJSONList :: [ShelleyGenesis c] -> Value #

toEncodingList :: [ShelleyGenesis c] -> Encoding #

omitField :: ShelleyGenesis c -> Bool #

Generic (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Associated Types

type Rep (ShelleyGenesis c) :: Type -> Type Source #

Crypto c => Show (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Crypto c => FromCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

fromCBOR :: Decoder s (ShelleyGenesis c)

label :: Proxy (ShelleyGenesis c) -> Text

Crypto c => ToCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toCBOR :: ShelleyGenesis c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyGenesis c) -> Size

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

Crypto c => DecCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

decCBOR :: Decoder s (ShelleyGenesis c)

dropCBOR :: Proxy (ShelleyGenesis c) -> Decoder s ()

label :: Proxy (ShelleyGenesis c) -> Text

Crypto c => EncCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

encCBOR :: ShelleyGenesis c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ShelleyGenesis c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ShelleyGenesis c] -> Size

Crypto c => Eq (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Crypto c => NoThunks (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

noThunks :: Context -> ShelleyGenesis c -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ShelleyGenesis c -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ShelleyGenesis c) -> String

type Rep (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

type Rep (ShelleyGenesis c) = D1 ('MetaData "ShelleyGenesis" "Cardano.Ledger.Shelley.Genesis" "cardano-ledger-shelley-1.9.0.0-7HgzAx4k96DEHFChwYPQhk" 'False) (C1 ('MetaCons "ShelleyGenesis" 'PrefixI 'True) (((S1 ('MetaSel ('Just "sgSystemStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UTCTime) :*: (S1 ('MetaSel ('Just "sgNetworkMagic") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32) :*: S1 ('MetaSel ('Just "sgNetworkId") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Network))) :*: ((S1 ('MetaSel ('Just "sgActiveSlotsCoeff") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 PositiveUnitInterval) :*: S1 ('MetaSel ('Just "sgSecurityParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64)) :*: (S1 ('MetaSel ('Just "sgEpochLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochSize) :*: S1 ('MetaSel ('Just "sgSlotsPerKESPeriod") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64)))) :*: (((S1 ('MetaSel ('Just "sgMaxKESEvolutions") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64) :*: S1 ('MetaSel ('Just "sgSlotLength") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NominalDiffTimeMicro)) :*: (S1 ('MetaSel ('Just "sgUpdateQuorum") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64) :*: S1 ('MetaSel ('Just "sgMaxLovelaceSupply") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word64))) :*: ((S1 ('MetaSel ('Just "sgProtocolParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PParams (ShelleyEra c))) :*: S1 ('MetaSel ('Just "sgGenDelegs") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'Genesis c) (GenDelegPair c)))) :*: (S1 ('MetaSel ('Just "sgInitialFunds") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ListMap (Addr c) Coin)) :*: S1 ('MetaSel ('Just "sgStaking") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (ShelleyGenesisStaking c)))))))

type family ShelleyLedgerEra era = (ledgerera :: Type) | ledgerera -> era where ... #

Equations

ShelleyLedgerEra ShelleyEra = StandardShelley 
ShelleyLedgerEra AllegraEra = StandardAllegra 
ShelleyLedgerEra MaryEra = StandardMary 
ShelleyLedgerEra AlonzoEra = StandardAlonzo 
ShelleyLedgerEra BabbageEra = StandardBabbage 
ShelleyLedgerEra ConwayEra = StandardConway 

data family SigningKey keyrole #

Instances

Instances details
IsString (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

IsString (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

IsString (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

IsString (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

IsString (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Show (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Show (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Show (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Show (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTypeProxy a => HasTypeProxy (SigningKey a) 
Instance details

Defined in Cardano.Api.Keys.Class

Associated Types

data AsType (SigningKey a) #

SerialiseAsBech32 (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsBech32 (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsBech32 (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsCBOR (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsCBOR (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsRawBytes (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsRawBytes (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

HasTextEnvelope (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

HasTextEnvelope (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

HasTextEnvelope (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

HasTextEnvelope (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

fromCBOR :: Decoder s (SigningKey KesKey)

label :: Proxy (SigningKey KesKey) -> Text

FromCBOR (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

fromCBOR :: Decoder s (SigningKey VrfKey)

label :: Proxy (SigningKey VrfKey) -> Text

FromCBOR (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: SigningKey ByronKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey ByronKey) -> Size

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

ToCBOR (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: SigningKey ByronKeyLegacy -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey ByronKeyLegacy) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey ByronKeyLegacy] -> Size

ToCBOR (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

toCBOR :: SigningKey KesKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey KesKey) -> Size

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

ToCBOR (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

toCBOR :: SigningKey VrfKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey VrfKey) -> Size

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

ToCBOR (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey CommitteeColdExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdExtendedKey] -> Size

ToCBOR (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey CommitteeColdKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdKey] -> Size

ToCBOR (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey CommitteeHotExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotExtendedKey] -> Size

ToCBOR (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey CommitteeHotKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotKey] -> Size

ToCBOR (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey DRepExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey DRepExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey DRepExtendedKey] -> Size

ToCBOR (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey DRepKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey DRepKey) -> Size

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

ToCBOR (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisDelegateExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateExtendedKey] -> Size

ToCBOR (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisDelegateKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateKey] -> Size

ToCBOR (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisExtendedKey] -> Size

ToCBOR (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisKey] -> Size

ToCBOR (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisUTxOKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisUTxOKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisUTxOKey] -> Size

ToCBOR (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey PaymentExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentExtendedKey] -> Size

ToCBOR (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey PaymentKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentKey] -> Size

ToCBOR (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey StakeExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakeExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakeExtendedKey] -> Size

ToCBOR (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey StakeKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakeKey) -> Size

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

ToCBOR (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey StakePoolKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakePoolKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakePoolKey] -> Size

newtype SigningKey ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

newtype SigningKey ByronKey = ByronSigningKey SigningKey
newtype SigningKey ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

newtype SigningKey KesKey 
Instance details

Defined in Cardano.Api.Keys.Praos

newtype SigningKey VrfKey 
Instance details

Defined in Cardano.Api.Keys.Praos

newtype SigningKey CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey GenesisDelegateExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey GenesisExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey GenesisUTxOKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey StakeExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey StakePoolKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType (SigningKey a) 
Instance details

Defined in Cardano.Api.Keys.Class

data family VerificationKey keyrole #

Instances

Instances details
FromJSON (VerificationKey PaymentKey) Source # 
Instance details

Defined in Hydra.Cardano.Api.VerificationKey

ToJSON (VerificationKey PaymentKey) Source # 
Instance details

Defined in Hydra.Cardano.Api.VerificationKey

IsString (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

IsString (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

IsString (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

IsString (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

IsString (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Show (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Show (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Show (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Show (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTypeProxy a => HasTypeProxy (VerificationKey a) 
Instance details

Defined in Cardano.Api.Keys.Class

Associated Types

data AsType (VerificationKey a) #

SerialiseAsBech32 (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsBech32 (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsBech32 (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsCBOR (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsCBOR (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsRawBytes (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsRawBytes (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

HasTextEnvelope (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

HasTextEnvelope (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

HasTextEnvelope (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

HasTextEnvelope (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

FromCBOR (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

FromCBOR (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: VerificationKey ByronKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey ByronKey) -> Size

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

ToCBOR (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: VerificationKey ByronKeyLegacy -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey ByronKeyLegacy) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey ByronKeyLegacy] -> Size

ToCBOR (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

toCBOR :: VerificationKey KesKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey KesKey) -> Size

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

ToCBOR (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

toCBOR :: VerificationKey VrfKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey VrfKey) -> Size

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

ToCBOR (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey CommitteeColdKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeColdKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeColdKey] -> Size

ToCBOR (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey CommitteeHotKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeHotKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeHotKey] -> Size

ToCBOR (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey DRepExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey DRepExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey DRepExtendedKey] -> Size

ToCBOR (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey DRepKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey DRepKey) -> Size

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

ToCBOR (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey GenesisDelegateKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisDelegateKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisDelegateKey] -> Size

ToCBOR (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey GenesisExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisExtendedKey] -> Size

ToCBOR (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey GenesisKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisKey] -> Size

ToCBOR (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey GenesisUTxOKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisUTxOKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisUTxOKey] -> Size

ToCBOR (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey PaymentExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentExtendedKey] -> Size

ToCBOR (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey PaymentKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentKey] -> Size

ToCBOR (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey StakeExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakeExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakeExtendedKey] -> Size

ToCBOR (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey StakeKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakeKey) -> Size

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

ToCBOR (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey StakePoolKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakePoolKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakePoolKey] -> Size

Eq (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Eq (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Eq (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Eq (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Eq (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

newtype VerificationKey ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

newtype VerificationKey KesKey 
Instance details

Defined in Cardano.Api.Keys.Praos

newtype VerificationKey VrfKey 
Instance details

Defined in Cardano.Api.Keys.Praos

newtype VerificationKey CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey GenesisDelegateExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey GenesisExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey GenesisUTxOKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey StakeExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey StakePoolKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType (VerificationKey a) 
Instance details

Defined in Cardano.Api.Keys.Class

newtype Coin #

Constructors

Coin 

Fields

Instances

Instances details
FromJSON Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

parseJSON :: Value -> Parser Coin #

parseJSONList :: Value -> Parser [Coin] #

omittedField :: Maybe Coin #

ToJSON Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toJSON :: Coin -> Value #

toEncoding :: Coin -> Encoding #

toJSONList :: [Coin] -> Value #

toEncodingList :: [Coin] -> Encoding #

omitField :: Coin -> Bool #

Monoid Coin 
Instance details

Defined in Cardano.Ledger.Coin

Semigroup Coin 
Instance details

Defined in Cardano.Ledger.Coin

Enum Coin 
Instance details

Defined in Cardano.Ledger.Coin

Generic Coin 
Instance details

Defined in Cardano.Ledger.Coin

Associated Types

type Rep Coin :: Type -> Type Source #

Methods

from :: Coin -> Rep Coin x Source #

to :: Rep Coin x -> Coin Source #

Show Coin 
Instance details

Defined in Cardano.Ledger.Coin

FromCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

fromCBOR :: Decoder s Coin

label :: Proxy Coin -> Text

ToCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toCBOR :: Coin -> Encoding

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

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

DecCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

decCBOR :: Decoder s Coin

dropCBOR :: Proxy Coin -> Decoder s ()

label :: Proxy Coin -> Text

EncCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

encCBOR :: Coin -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Coin -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Coin] -> Size

Compactible Coin 
Instance details

Defined in Cardano.Ledger.Coin

Associated Types

data CompactForm Coin

Methods

toCompact :: Coin -> Maybe (CompactForm Coin)

fromCompact :: CompactForm Coin -> Coin

Val Coin 
Instance details

Defined in Cardano.Ledger.Val

Methods

zero :: Coin

(<+>) :: Coin -> Coin -> Coin

(<×>) :: Integral i => i -> Coin -> Coin

(<->) :: Coin -> Coin -> Coin

isZero :: Coin -> Bool

coin :: Coin -> Coin

modifyCoin :: (Coin -> Coin) -> Coin -> Coin

size :: Coin -> Integer

pointwise :: (Integer -> Integer -> Bool) -> Coin -> Coin -> Bool

isAdaOnly :: Coin -> Bool

isAdaOnlyCompact :: CompactForm Coin -> Bool

coinCompact :: CompactForm Coin -> CompactForm Coin

injectCompact :: CompactForm Coin -> CompactForm Coin

modifyCompactCoin :: (CompactForm Coin -> CompactForm Coin) -> CompactForm Coin -> CompactForm Coin

NFData Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

rnf :: Coin -> () Source #

Eq Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

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

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

Ord Coin 
Instance details

Defined in Cardano.Ledger.Coin

Abelian Coin 
Instance details

Defined in Cardano.Ledger.Coin

Group Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

invert :: Coin -> Coin

(~~) :: Coin -> Coin -> Coin

pow :: Integral x => Coin -> x -> Coin

HeapWords Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

heapWords :: Coin -> Int

NoThunks Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

noThunks :: Context -> Coin -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Coin -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy Coin -> String

PartialOrd Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

(<=) :: Coin -> Coin -> Bool

(>=) :: Coin -> Coin -> Bool

(==) :: Coin -> Coin -> Bool

(/=) :: Coin -> Coin -> Bool

(<) :: Coin -> Coin -> Bool

(>) :: Coin -> Coin -> Bool

compare :: Coin -> Coin -> Maybe Ordering

Inject Coin Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

inject :: Coin -> Coin

Inject Coin DeltaCoin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

inject :: Coin -> DeltaCoin

Inject Coin (MaryValue c) 
Instance details

Defined in Cardano.Ledger.Mary.Value

Methods

inject :: Coin -> MaryValue c

FromJSON (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

parseJSON :: Value -> Parser (CompactForm Coin) #

parseJSONList :: Value -> Parser [CompactForm Coin] #

omittedField :: Maybe (CompactForm Coin) #

ToJSON (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toJSON :: CompactForm Coin -> Value #

toEncoding :: CompactForm Coin -> Encoding #

toJSONList :: [CompactForm Coin] -> Value #

toEncodingList :: [CompactForm Coin] -> Encoding #

omitField :: CompactForm Coin -> Bool #

Monoid (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

mempty :: CompactForm Coin Source #

mappend :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin Source #

mconcat :: [CompactForm Coin] -> CompactForm Coin Source #

Semigroup (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

(<>) :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin Source #

sconcat :: NonEmpty (CompactForm Coin) -> CompactForm Coin Source #

stimes :: Integral b => b -> CompactForm Coin -> CompactForm Coin Source #

Show (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

showsPrec :: Int -> CompactForm Coin -> ShowS Source #

show :: CompactForm Coin -> String Source #

showList :: [CompactForm Coin] -> ShowS Source #

ToCBOR (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toCBOR :: CompactForm Coin -> Encoding

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

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

DecCBOR (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

decCBOR :: Decoder s (CompactForm Coin)

dropCBOR :: Proxy (CompactForm Coin) -> Decoder s ()

label :: Proxy (CompactForm Coin) -> Text

EncCBOR (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

encCBOR :: CompactForm Coin -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (CompactForm Coin) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CompactForm Coin] -> Size

NFData (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

rnf :: CompactForm Coin -> () Source #

Eq (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

(==) :: CompactForm Coin -> CompactForm Coin -> Bool Source #

(/=) :: CompactForm Coin -> CompactForm Coin -> Bool Source #

Ord (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

compare :: CompactForm Coin -> CompactForm Coin -> Ordering Source #

(<) :: CompactForm Coin -> CompactForm Coin -> Bool Source #

(<=) :: CompactForm Coin -> CompactForm Coin -> Bool Source #

(>) :: CompactForm Coin -> CompactForm Coin -> Bool Source #

(>=) :: CompactForm Coin -> CompactForm Coin -> Bool Source #

max :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin Source #

min :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin Source #

Abelian (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Group (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

invert :: CompactForm Coin -> CompactForm Coin

(~~) :: CompactForm Coin -> CompactForm Coin -> CompactForm Coin

pow :: Integral x => CompactForm Coin -> x -> CompactForm Coin

HeapWords (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

heapWords :: CompactForm Coin -> Int

NoThunks (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

noThunks :: Context -> CompactForm Coin -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> CompactForm Coin -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (CompactForm Coin) -> String

Prim (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

sizeOf# :: CompactForm Coin -> Int#

alignment# :: CompactForm Coin -> Int#

indexByteArray# :: ByteArray# -> Int# -> CompactForm Coin

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, CompactForm Coin #)

writeByteArray# :: MutableByteArray# s -> Int# -> CompactForm Coin -> State# s -> State# s

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> CompactForm Coin -> State# s -> State# s

indexOffAddr# :: Addr# -> Int# -> CompactForm Coin

readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, CompactForm Coin #)

writeOffAddr# :: Addr# -> Int# -> CompactForm Coin -> State# s -> State# s

setOffAddr# :: Addr# -> Int# -> Int# -> CompactForm Coin -> State# s -> State# s

type Rep Coin 
Instance details

Defined in Cardano.Ledger.Coin

type Rep Coin = D1 ('MetaData "Coin" "Cardano.Ledger.Coin" "cardano-ledger-core-1.10.0.0-IIS5MSjTn5M2E69fpQvkaS" 'True) (C1 ('MetaCons "Coin" 'PrefixI 'True) (S1 ('MetaSel ('Just "unCoin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)))
newtype CompactForm Coin 
Instance details

Defined in Cardano.Ledger.Coin

newtype CompactForm Coin = CompactCoin Word64

data BlockHeader #

Instances

Instances details
Arbitrary BlockHeader Source # 
Instance details

Defined in Hydra.Cardano.Api.BlockHeader

HasTypeProxy BlockHeader 
Instance details

Defined in Cardano.Api.Block

Associated Types

data AsType BlockHeader #

FromJSON (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

Methods

parseJSON :: Value -> Parser (Hash BlockHeader) #

parseJSONList :: Value -> Parser [Hash BlockHeader] #

omittedField :: Maybe (Hash BlockHeader) #

ToJSON (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

IsString (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

Show (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

SerialiseAsRawBytes (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

Eq (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

Ord (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

data AsType BlockHeader 
Instance details

Defined in Cardano.Api.Block

newtype Hash BlockHeader 
Instance details

Defined in Cardano.Api.Block

data ChainPoint #

data CtxTx #

Instances

Instances details
IsShelleyBasedEra era => FromJSON (TxOut CtxTx era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

parseJSON :: Value -> Parser (TxOut CtxTx era) #

parseJSONList :: Value -> Parser [TxOut CtxTx era] #

omittedField :: Maybe (TxOut CtxTx era) #

data CtxUTxO #

Instances

Instances details
IsShelleyBasedEra era => FromJSON (TxOut CtxUTxO era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

parseJSON :: Value -> Parser (TxOut CtxUTxO era) #

parseJSONList :: Value -> Parser [TxOut CtxUTxO era] #

omittedField :: Maybe (TxOut CtxUTxO era) #

data ExecutionUnits #

Instances

Instances details
FromJSON ExecutionUnits 
Instance details

Defined in Cardano.Api.Script

Methods

parseJSON :: Value -> Parser ExecutionUnits #

parseJSONList :: Value -> Parser [ExecutionUnits] #

omittedField :: Maybe ExecutionUnits #

ToJSON ExecutionUnits 
Instance details

Defined in Cardano.Api.Script

Show ExecutionUnits 
Instance details

Defined in Cardano.Api.Script

FromCBOR ExecutionUnits 
Instance details

Defined in Cardano.Api.Script

ToCBOR ExecutionUnits 
Instance details

Defined in Cardano.Api.Script

Methods

toCBOR :: ExecutionUnits -> Encoding

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

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

Eq ExecutionUnits 
Instance details

Defined in Cardano.Api.Script

data NetworkId #

Constructors

Mainnet 
Testnet !NetworkMagic 

Instances

Instances details
FromJSON NetworkId Source # 
Instance details

Defined in Hydra.Cardano.Api.NetworkId

Methods

parseJSON :: Value -> Parser NetworkId #

parseJSONList :: Value -> Parser [NetworkId] #

omittedField :: Maybe NetworkId #

ToJSON NetworkId Source # 
Instance details

Defined in Hydra.Cardano.Api.NetworkId

Methods

toJSON :: NetworkId -> Value #

toEncoding :: NetworkId -> Encoding #

toJSONList :: [NetworkId] -> Value #

toEncodingList :: [NetworkId] -> Encoding #

omitField :: NetworkId -> Bool #

Show NetworkId 
Instance details

Defined in Cardano.Api.NetworkId

Eq NetworkId 
Instance details

Defined in Cardano.Api.NetworkId

newtype PolicyId #

Constructors

PolicyId 

Instances

Instances details
Arbitrary PolicyId Source # 
Instance details

Defined in Hydra.Cardano.Api.PolicyId

FromJSON PolicyId 
Instance details

Defined in Cardano.Api.Value

Methods

parseJSON :: Value -> Parser PolicyId #

parseJSONList :: Value -> Parser [PolicyId] #

omittedField :: Maybe PolicyId #

ToJSON PolicyId 
Instance details

Defined in Cardano.Api.Value

Methods

toJSON :: PolicyId -> Value #

toEncoding :: PolicyId -> Encoding #

toJSONList :: [PolicyId] -> Value #

toEncodingList :: [PolicyId] -> Encoding #

omitField :: PolicyId -> Bool #

IsString PolicyId 
Instance details

Defined in Cardano.Api.Value

Show PolicyId 
Instance details

Defined in Cardano.Api.Value

HasTypeProxy PolicyId 
Instance details

Defined in Cardano.Api.Value

Associated Types

data AsType PolicyId #

SerialiseAsRawBytes PolicyId 
Instance details

Defined in Cardano.Api.Value

Eq PolicyId 
Instance details

Defined in Cardano.Api.Value

Ord PolicyId 
Instance details

Defined in Cardano.Api.Value

data AsType PolicyId 
Instance details

Defined in Cardano.Api.Value

data ScriptData #

Instances

Instances details
Arbitrary ScriptData Source # 
Instance details

Defined in Hydra.Cardano.Api.ScriptData

FromJSON ScriptData Source # 
Instance details

Defined in Hydra.Cardano.Api.ScriptData

Methods

parseJSON :: Value -> Parser ScriptData #

parseJSONList :: Value -> Parser [ScriptData] #

omittedField :: Maybe ScriptData #

ToJSON ScriptData Source # 
Instance details

Defined in Hydra.Cardano.Api.ScriptData

Methods

toJSON :: ScriptData -> Value #

toEncoding :: ScriptData -> Encoding #

toJSONList :: [ScriptData] -> Value #

toEncodingList :: [ScriptData] -> Encoding #

omitField :: ScriptData -> Bool #

Show ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

HasTypeProxy ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

Associated Types

data AsType ScriptData #

SerialiseAsCBOR ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

FromCBOR ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

Methods

fromCBOR :: Decoder s ScriptData

label :: Proxy ScriptData -> Text

ToCBOR ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

Methods

toCBOR :: ScriptData -> Encoding

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

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

Eq ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

Ord ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

FromJSON (Hash ScriptData) 
Instance details

Defined in Cardano.Api.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.ScriptData

Methods

fromJSONKey :: FromJSONKeyFunction (Hash ScriptData)

fromJSONKeyList :: FromJSONKeyFunction [Hash ScriptData]

ToJSON (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

Methods

toJSON :: Hash ScriptData -> Value #

toEncoding :: Hash ScriptData -> Encoding #

toJSONList :: [Hash ScriptData] -> Value #

toEncodingList :: [Hash ScriptData] -> Encoding #

omitField :: Hash ScriptData -> Bool #

ToJSONKey (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

Methods

toJSONKey :: ToJSONKeyFunction (Hash ScriptData)

toJSONKeyList :: ToJSONKeyFunction [Hash ScriptData]

IsString (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

Show (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

SerialiseAsRawBytes (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

Eq (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

Ord (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

data AsType ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

newtype Hash ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

data ScriptDatum witctx where #

Instances

Instances details
Show (ScriptDatum witctx) 
Instance details

Defined in Cardano.Api.Script

Methods

showsPrec :: Int -> ScriptDatum witctx -> ShowS Source #

show :: ScriptDatum witctx -> String Source #

showList :: [ScriptDatum witctx] -> ShowS Source #

Eq (ScriptDatum witctx) 
Instance details

Defined in Cardano.Api.Script

Methods

(==) :: ScriptDatum witctx -> ScriptDatum witctx -> Bool Source #

(/=) :: ScriptDatum witctx -> ScriptDatum witctx -> Bool Source #

newtype ScriptHash #

Constructors

ScriptHash (ScriptHash StandardCrypto) 

Instances

Instances details
Arbitrary ScriptHash Source # 
Instance details

Defined in Hydra.Cardano.Api.ScriptHash

FromJSON ScriptHash 
Instance details

Defined in Cardano.Api.Script

Methods

parseJSON :: Value -> Parser ScriptHash #

parseJSONList :: Value -> Parser [ScriptHash] #

omittedField :: Maybe ScriptHash #

ToJSON ScriptHash 
Instance details

Defined in Cardano.Api.Script

Methods

toJSON :: ScriptHash -> Value #

toEncoding :: ScriptHash -> Encoding #

toJSONList :: [ScriptHash] -> Value #

toEncodingList :: [ScriptHash] -> Encoding #

omitField :: ScriptHash -> Bool #

IsString ScriptHash 
Instance details

Defined in Cardano.Api.Script

Show ScriptHash 
Instance details

Defined in Cardano.Api.Script

HasTypeProxy ScriptHash 
Instance details

Defined in Cardano.Api.Script

Associated Types

data AsType ScriptHash #

SerialiseAsRawBytes ScriptHash 
Instance details

Defined in Cardano.Api.Script

Eq ScriptHash 
Instance details

Defined in Cardano.Api.Script

Ord ScriptHash 
Instance details

Defined in Cardano.Api.Script

data AsType ScriptHash 
Instance details

Defined in Cardano.Api.Script

newtype TxId #

Constructors

TxId (Hash StandardCrypto EraIndependentTxBody) 

Instances

Instances details
FromJSON TxId 
Instance details

Defined in Cardano.Api.TxIn

Methods

parseJSON :: Value -> Parser TxId #

parseJSONList :: Value -> Parser [TxId] #

omittedField :: Maybe TxId #

FromJSONKey TxId 
Instance details

Defined in Cardano.Api.TxIn

Methods

fromJSONKey :: FromJSONKeyFunction TxId

fromJSONKeyList :: FromJSONKeyFunction [TxId]

ToJSON TxId 
Instance details

Defined in Cardano.Api.TxIn

Methods

toJSON :: TxId -> Value #

toEncoding :: TxId -> Encoding #

toJSONList :: [TxId] -> Value #

toEncodingList :: [TxId] -> Encoding #

omitField :: TxId -> Bool #

ToJSONKey TxId 
Instance details

Defined in Cardano.Api.TxIn

Methods

toJSONKey :: ToJSONKeyFunction TxId

toJSONKeyList :: ToJSONKeyFunction [TxId]

IsString TxId 
Instance details

Defined in Cardano.Api.TxIn

Show TxId 
Instance details

Defined in Cardano.Api.TxIn

HasTypeProxy TxId 
Instance details

Defined in Cardano.Api.TxIn

Associated Types

data AsType TxId #

SerialiseAsRawBytes TxId 
Instance details

Defined in Cardano.Api.TxIn

FromCBOR TxId Source # 
Instance details

Defined in Hydra.Cardano.Api.TxId

Methods

fromCBOR :: Decoder s TxId

label :: Proxy TxId -> Text

ToCBOR TxId Source # 
Instance details

Defined in Hydra.Cardano.Api.TxId

Methods

toCBOR :: TxId -> Encoding

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

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

Eq TxId 
Instance details

Defined in Cardano.Api.TxIn

Methods

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

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

Ord TxId 
Instance details

Defined in Cardano.Api.TxIn

data AsType TxId 
Instance details

Defined in Cardano.Api.TxIn

data TxIn #

Constructors

TxIn TxId TxIx 

Instances

Instances details
Arbitrary TxIn Source # 
Instance details

Defined in Hydra.Cardano.Api.TxIn

Methods

arbitrary :: Gen TxIn #

shrink :: TxIn -> [TxIn] #

FromJSON TxIn 
Instance details

Defined in Cardano.Api.TxIn

Methods

parseJSON :: Value -> Parser TxIn #

parseJSONList :: Value -> Parser [TxIn] #

omittedField :: Maybe TxIn #

FromJSONKey TxIn 
Instance details

Defined in Cardano.Api.TxIn

Methods

fromJSONKey :: FromJSONKeyFunction TxIn

fromJSONKeyList :: FromJSONKeyFunction [TxIn]

ToJSON TxIn 
Instance details

Defined in Cardano.Api.TxIn

Methods

toJSON :: TxIn -> Value #

toEncoding :: TxIn -> Encoding #

toJSONList :: [TxIn] -> Value #

toEncodingList :: [TxIn] -> Encoding #

omitField :: TxIn -> Bool #

ToJSONKey TxIn 
Instance details

Defined in Cardano.Api.TxIn

Methods

toJSONKey :: ToJSONKeyFunction TxIn

toJSONKeyList :: ToJSONKeyFunction [TxIn]

Show TxIn 
Instance details

Defined in Cardano.Api.TxIn

Eq TxIn 
Instance details

Defined in Cardano.Api.TxIn

Methods

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

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

Ord TxIn 
Instance details

Defined in Cardano.Api.TxIn

Pretty TxIn 
Instance details

Defined in Cardano.Api.TxIn

Methods

pretty :: TxIn -> Doc ann #

prettyList :: [TxIn] -> Doc ann #

data TxOutValue era where #

Constructors

TxOutValueByron :: forall era. Coin -> TxOutValue era 
TxOutValueShelleyBased :: forall era. (Eq (Value (ShelleyLedgerEra era)), Show (Value (ShelleyLedgerEra era))) => ShelleyBasedEra era -> Value (ShelleyLedgerEra era) -> TxOutValue era 

Instances

Instances details
IsShelleyBasedEra era => FromJSON (TxOutValue era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

parseJSON :: Value -> Parser (TxOutValue era) #

parseJSONList :: Value -> Parser [TxOutValue era] #

omittedField :: Maybe (TxOutValue era) #

IsCardanoEra era => ToJSON (TxOutValue era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

toJSON :: TxOutValue era -> Value #

toEncoding :: TxOutValue era -> Encoding #

toJSONList :: [TxOutValue era] -> Value #

toEncodingList :: [TxOutValue era] -> Encoding #

omitField :: TxOutValue era -> Bool #

Show (TxOutValue era) 
Instance details

Defined in Cardano.Api.Tx.Body

Eq (TxOutValue era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

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

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

data Value #

Instances

Instances details
FromJSON Value 
Instance details

Defined in Cardano.Api.Value

Methods

parseJSON :: Value0 -> Parser Value #

parseJSONList :: Value0 -> Parser [Value] #

omittedField :: Maybe Value #

ToJSON Value 
Instance details

Defined in Cardano.Api.Value

Methods

toJSON :: Value -> Value0 #

toEncoding :: Value -> Encoding #

toJSONList :: [Value] -> Value0 #

toEncodingList :: [Value] -> Encoding #

omitField :: Value -> Bool #

Monoid Value 
Instance details

Defined in Cardano.Api.Value

Semigroup Value 
Instance details

Defined in Cardano.Api.Value

Show Value 
Instance details

Defined in Cardano.Api.Value

Eq Value 
Instance details

Defined in Cardano.Api.Value

Methods

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

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

class FromJSON a #

Instances

Instances details
FromJSON Key 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Key #

parseJSONList :: Value -> Parser [Key] #

omittedField :: Maybe Key #

FromJSON DotNetTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser DotNetTime #

parseJSONList :: Value -> Parser [DotNetTime] #

omittedField :: Maybe DotNetTime #

FromJSON Value 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Value #

parseJSONList :: Value -> Parser [Value] #

omittedField :: Maybe Value #

FromJSON Version 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Version #

parseJSONList :: Value -> Parser [Version] #

omittedField :: Maybe Version #

FromJSON CTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser CTime #

parseJSONList :: Value -> Parser [CTime] #

omittedField :: Maybe CTime #

FromJSON Void 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Void #

parseJSONList :: Value -> Parser [Void] #

omittedField :: Maybe Void #

FromJSON Int16 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int16 #

parseJSONList :: Value -> Parser [Int16] #

omittedField :: Maybe Int16 #

FromJSON Int32 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int32 #

parseJSONList :: Value -> Parser [Int32] #

omittedField :: Maybe Int32 #

FromJSON Int64 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int64 #

parseJSONList :: Value -> Parser [Int64] #

omittedField :: Maybe Int64 #

FromJSON Int8 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int8 #

parseJSONList :: Value -> Parser [Int8] #

omittedField :: Maybe Int8 #

FromJSON Word16 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word16 #

parseJSONList :: Value -> Parser [Word16] #

omittedField :: Maybe Word16 #

FromJSON Word32 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word32 #

parseJSONList :: Value -> Parser [Word32] #

omittedField :: Maybe Word32 #

FromJSON Word64 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word64 #

parseJSONList :: Value -> Parser [Word64] #

omittedField :: Maybe Word64 #

FromJSON Word8 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word8 #

parseJSONList :: Value -> Parser [Word8] #

omittedField :: Maybe Word8 #

FromJSON StakeAddress 
Instance details

Defined in Cardano.Api.Address

Methods

parseJSON :: Value -> Parser StakeAddress #

parseJSONList :: Value -> Parser [StakeAddress] #

omittedField :: Maybe StakeAddress #

FromJSON ChainPoint 
Instance details

Defined in Cardano.Api.Block

Methods

parseJSON :: Value -> Parser ChainPoint #

parseJSONList :: Value -> Parser [ChainPoint] #

omittedField :: Maybe ChainPoint #

FromJSON AnyShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

FromJSON AnyCardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

parseJSON :: Value -> Parser AnyCardanoEra #

parseJSONList :: Value -> Parser [AnyCardanoEra] #

omittedField :: Maybe AnyCardanoEra #

FromJSON NodeConfig 
Instance details

Defined in Cardano.Api.LedgerState

Methods

parseJSON :: Value -> Parser NodeConfig #

parseJSONList :: Value -> Parser [NodeConfig] #

omittedField :: Maybe NodeConfig #

FromJSON NetworkId Source # 
Instance details

Defined in Hydra.Cardano.Api.NetworkId

Methods

parseJSON :: Value -> Parser NetworkId #

parseJSONList :: Value -> Parser [NetworkId] #

omittedField :: Maybe NetworkId #

FromJSON CostModels 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

parseJSON :: Value -> Parser CostModels #

parseJSONList :: Value -> Parser [CostModels] #

omittedField :: Maybe CostModels #

FromJSON ExecutionUnitPrices 
Instance details

Defined in Cardano.Api.ProtocolParameters

FromJSON PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

parseJSON :: Value -> Parser PraosNonce #

parseJSONList :: Value -> Parser [PraosNonce] #

omittedField :: Maybe PraosNonce #

FromJSON ProtocolParameters 
Instance details

Defined in Cardano.Api.ProtocolParameters

FromJSON DelegationsAndRewards 
Instance details

Defined in Cardano.Api.Rewards

FromJSON AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

FromJSON ExecutionUnits 
Instance details

Defined in Cardano.Api.Script

Methods

parseJSON :: Value -> Parser ExecutionUnits #

parseJSONList :: Value -> Parser [ExecutionUnits] #

omittedField :: Maybe ExecutionUnits #

FromJSON ScriptHash 
Instance details

Defined in Cardano.Api.Script

Methods

parseJSON :: Value -> Parser ScriptHash #

parseJSONList :: Value -> Parser [ScriptHash] #

omittedField :: Maybe ScriptHash #

FromJSON ScriptInAnyLang 
Instance details

Defined in Cardano.Api.Script

FromJSON SimpleScript 
Instance details

Defined in Cardano.Api.Script

Methods

parseJSON :: Value -> Parser SimpleScript #

parseJSONList :: Value -> Parser [SimpleScript] #

omittedField :: Maybe SimpleScript #

FromJSON HashableScriptData Source # 
Instance details

Defined in Hydra.Cardano.Api.ScriptData

FromJSON ScriptData Source # 
Instance details

Defined in Hydra.Cardano.Api.ScriptData

Methods

parseJSON :: Value -> Parser ScriptData #

parseJSONList :: Value -> Parser [ScriptData] #

omittedField :: Maybe ScriptData #

FromJSON TextEnvelopeCddl 
Instance details

Defined in Cardano.Api.SerialiseLedgerCddl

FromJSON TextEnvelope 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Methods

parseJSON :: Value -> Parser TextEnvelope #

parseJSONList :: Value -> Parser [TextEnvelope] #

omittedField :: Maybe TextEnvelope #

FromJSON TextEnvelopeDescr 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

FromJSON TextEnvelopeType 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

FromJSON StakePoolMetadata 
Instance details

Defined in Cardano.Api.StakePoolMetadata

FromJSON TxId 
Instance details

Defined in Cardano.Api.TxIn

Methods

parseJSON :: Value -> Parser TxId #

parseJSONList :: Value -> Parser [TxId] #

omittedField :: Maybe TxId #

FromJSON TxIn 
Instance details

Defined in Cardano.Api.TxIn

Methods

parseJSON :: Value -> Parser TxIn #

parseJSONList :: Value -> Parser [TxIn] #

omittedField :: Maybe TxIn #

FromJSON TxIx 
Instance details

Defined in Cardano.Api.TxIn

Methods

parseJSON :: Value -> Parser TxIx #

parseJSONList :: Value -> Parser [TxIx] #

omittedField :: Maybe TxIx #

FromJSON AssetName 
Instance details

Defined in Cardano.Api.Value

Methods

parseJSON :: Value -> Parser AssetName #

parseJSONList :: Value -> Parser [AssetName] #

omittedField :: Maybe AssetName #

FromJSON PolicyId 
Instance details

Defined in Cardano.Api.Value

Methods

parseJSON :: Value -> Parser PolicyId #

parseJSONList :: Value -> Parser [PolicyId] #

omittedField :: Maybe PolicyId #

FromJSON Quantity 
Instance details

Defined in Cardano.Api.Value

Methods

parseJSON :: Value -> Parser Quantity #

parseJSONList :: Value -> Parser [Quantity] #

omittedField :: Maybe Quantity #

FromJSON Value 
Instance details

Defined in Cardano.Api.Value

Methods

parseJSON :: Value0 -> Parser Value #

parseJSONList :: Value0 -> Parser [Value] #

omittedField :: Maybe Value #

FromJSON ValueNestedRep 
Instance details

Defined in Cardano.Api.Value

Methods

parseJSON :: Value -> Parser ValueNestedRep #

parseJSONList :: Value -> Parser [ValueNestedRep] #

omittedField :: Maybe ValueNestedRep #

FromJSON ProtocolMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Methods

parseJSON :: Value -> Parser ProtocolMagic #

parseJSONList :: Value -> Parser [ProtocolMagic] #

omittedField :: Maybe ProtocolMagic #

FromJSON ProtocolMagicId 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Methods

parseJSON :: Value -> Parser ProtocolMagicId #

parseJSONList :: Value -> Parser [ProtocolMagicId] #

omittedField :: Maybe ProtocolMagicId #

FromJSON RequiresNetworkMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Methods

parseJSON :: Value -> Parser RequiresNetworkMagic #

parseJSONList :: Value -> Parser [RequiresNetworkMagic] #

omittedField :: Maybe RequiresNetworkMagic #

FromJSON RedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.VerificationKey

Methods

parseJSON :: Value -> Parser RedeemVerificationKey #

parseJSONList :: Value -> Parser [RedeemVerificationKey] #

omittedField :: Maybe RedeemVerificationKey #

FromJSON VerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

Methods

parseJSON :: Value -> Parser VerificationKey #

parseJSONList :: Value -> Parser [VerificationKey] #

omittedField :: Maybe VerificationKey #

FromJSON AlonzoGenesis 
Instance details

Defined in Cardano.Ledger.Alonzo.Genesis

Methods

parseJSON :: Value -> Parser AlonzoGenesis #

parseJSONList :: Value -> Parser [AlonzoGenesis] #

omittedField :: Maybe AlonzoGenesis #

FromJSON CoinPerWord 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Methods

parseJSON :: Value -> Parser CoinPerWord #

parseJSONList :: Value -> Parser [CoinPerWord] #

omittedField :: Maybe CoinPerWord #

FromJSON OrdExUnits 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Methods

parseJSON :: Value -> Parser OrdExUnits #

parseJSONList :: Value -> Parser [OrdExUnits] #

omittedField :: Maybe OrdExUnits #

FromJSON CoinPerByte 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Methods

parseJSON :: Value -> Parser CoinPerByte #

parseJSONList :: Value -> Parser [CoinPerByte] #

omittedField :: Maybe CoinPerByte #

FromJSON Version 
Instance details

Defined in Cardano.Ledger.Binary.Version

Methods

parseJSON :: Value -> Parser Version #

parseJSONList :: Value -> Parser [Version] #

omittedField :: Maybe Version #

FromJSON DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

parseJSON :: Value -> Parser DRepVotingThresholds #

parseJSONList :: Value -> Parser [DRepVotingThresholds] #

omittedField :: Maybe DRepVotingThresholds #

FromJSON PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

parseJSON :: Value -> Parser PoolVotingThresholds #

parseJSONList :: Value -> Parser [PoolVotingThresholds] #

omittedField :: Maybe PoolVotingThresholds #

FromJSON DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser DnsName #

parseJSONList :: Value -> Parser [DnsName] #

omittedField :: Maybe DnsName #

FromJSON EpochInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser EpochInterval #

parseJSONList :: Value -> Parser [EpochInterval] #

omittedField :: Maybe EpochInterval #

FromJSON Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser Network #

parseJSONList :: Value -> Parser [Network] #

omittedField :: Maybe Network #

FromJSON NonNegativeInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser NonNegativeInterval #

parseJSONList :: Value -> Parser [NonNegativeInterval] #

omittedField :: Maybe NonNegativeInterval #

FromJSON Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser Nonce #

parseJSONList :: Value -> Parser [Nonce] #

omittedField :: Maybe Nonce #

FromJSON Port 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser Port #

parseJSONList :: Value -> Parser [Port] #

omittedField :: Maybe Port #

FromJSON PositiveInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser PositiveInterval #

parseJSONList :: Value -> Parser [PositiveInterval] #

omittedField :: Maybe PositiveInterval #

FromJSON PositiveUnitInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser PositiveUnitInterval #

parseJSONList :: Value -> Parser [PositiveUnitInterval] #

omittedField :: Maybe PositiveUnitInterval #

FromJSON ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser ProtVer #

parseJSONList :: Value -> Parser [ProtVer] #

omittedField :: Maybe ProtVer #

FromJSON UnitInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser UnitInterval #

parseJSONList :: Value -> Parser [UnitInterval] #

omittedField :: Maybe UnitInterval #

FromJSON Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser Url #

parseJSONList :: Value -> Parser [Url] #

omittedField :: Maybe Url #

FromJSON Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

parseJSON :: Value -> Parser Coin #

parseJSONList :: Value -> Parser [Coin] #

omittedField :: Maybe Coin #

FromJSON DeltaCoin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

parseJSON :: Value -> Parser DeltaCoin #

parseJSONList :: Value -> Parser [DeltaCoin] #

omittedField :: Maybe DeltaCoin #

FromJSON CostModels 
Instance details

Defined in Cardano.Ledger.Plutus.CostModels

Methods

parseJSON :: Value -> Parser CostModels #

parseJSONList :: Value -> Parser [CostModels] #

omittedField :: Maybe CostModels #

FromJSON ExUnits 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

parseJSON :: Value -> Parser ExUnits #

parseJSONList :: Value -> Parser [ExUnits] #

omittedField :: Maybe ExUnits #

FromJSON Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

parseJSON :: Value -> Parser Prices #

parseJSONList :: Value -> Parser [Prices] #

omittedField :: Maybe Prices #

FromJSON Language 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

parseJSON :: Value -> Parser Language #

parseJSONList :: Value -> Parser [Language] #

omittedField :: Maybe Language #

FromJSON PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

parseJSON :: Value -> Parser PoolMetadata #

parseJSONList :: Value -> Parser [PoolMetadata] #

omittedField :: Maybe PoolMetadata #

FromJSON StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

parseJSON :: Value -> Parser StakePoolRelay #

parseJSONList :: Value -> Parser [StakePoolRelay] #

omittedField :: Maybe StakePoolRelay #

FromJSON NominalDiffTimeMicro 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

parseJSON :: Value -> Parser NominalDiffTimeMicro #

parseJSONList :: Value -> Parser [NominalDiffTimeMicro] #

omittedField :: Maybe NominalDiffTimeMicro #

FromJSON BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

parseJSON :: Value -> Parser BlockNo #

parseJSONList :: Value -> Parser [BlockNo] #

omittedField :: Maybe BlockNo #

FromJSON EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

parseJSON :: Value -> Parser EpochNo #

parseJSONList :: Value -> Parser [EpochNo] #

omittedField :: Maybe EpochNo #

FromJSON EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Methods

parseJSON :: Value -> Parser EpochSize #

parseJSONList :: Value -> Parser [EpochSize] #

omittedField :: Maybe EpochSize #

FromJSON SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

parseJSON :: Value -> Parser SlotNo #

parseJSONList :: Value -> Parser [SlotNo] #

omittedField :: Maybe SlotNo #

FromJSON RelativeTime 
Instance details

Defined in Cardano.Slotting.Time

Methods

parseJSON :: Value -> Parser RelativeTime #

parseJSONList :: Value -> Parser [RelativeTime] #

omittedField :: Maybe RelativeTime #

FromJSON SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

parseJSON :: Value -> Parser SystemStart #

parseJSONList :: Value -> Parser [SystemStart] #

omittedField :: Maybe SystemStart #

FromJSON IntSet 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser IntSet #

parseJSONList :: Value -> Parser [IntSet] #

omittedField :: Maybe IntSet #

FromJSON Ordering 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Ordering #

parseJSONList :: Value -> Parser [Ordering] #

omittedField :: Maybe Ordering #

FromJSON URI 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser URI #

parseJSONList :: Value -> Parser [URI] #

omittedField :: Maybe URI #

FromJSON Scientific 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Scientific #

parseJSONList :: Value -> Parser [Scientific] #

omittedField :: Maybe Scientific #

FromJSON Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Text #

parseJSONList :: Value -> Parser [Text] #

omittedField :: Maybe Text #

FromJSON Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Text #

parseJSONList :: Value -> Parser [Text] #

omittedField :: Maybe Text #

FromJSON ShortText 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser ShortText #

parseJSONList :: Value -> Parser [ShortText] #

omittedField :: Maybe ShortText #

FromJSON CalendarDiffDays 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON Day 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Day #

parseJSONList :: Value -> Parser [Day] #

omittedField :: Maybe Day #

FromJSON Month 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Month #

parseJSONList :: Value -> Parser [Month] #

omittedField :: Maybe Month #

FromJSON Quarter 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Quarter #

parseJSONList :: Value -> Parser [Quarter] #

omittedField :: Maybe Quarter #

FromJSON QuarterOfYear 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser QuarterOfYear #

parseJSONList :: Value -> Parser [QuarterOfYear] #

omittedField :: Maybe QuarterOfYear #

FromJSON DayOfWeek 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser DayOfWeek #

parseJSONList :: Value -> Parser [DayOfWeek] #

omittedField :: Maybe DayOfWeek #

FromJSON DiffTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser DiffTime #

parseJSONList :: Value -> Parser [DiffTime] #

omittedField :: Maybe DiffTime #

FromJSON NominalDiffTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON SystemTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser SystemTime #

parseJSONList :: Value -> Parser [SystemTime] #

omittedField :: Maybe SystemTime #

FromJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser UTCTime #

parseJSONList :: Value -> Parser [UTCTime] #

omittedField :: Maybe UTCTime #

FromJSON CalendarDiffTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSON LocalTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser LocalTime #

parseJSONList :: Value -> Parser [LocalTime] #

omittedField :: Maybe LocalTime #

FromJSON TimeOfDay 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser TimeOfDay #

parseJSONList :: Value -> Parser [TimeOfDay] #

omittedField :: Maybe TimeOfDay #

FromJSON ZonedTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser ZonedTime #

parseJSONList :: Value -> Parser [ZonedTime] #

omittedField :: Maybe ZonedTime #

FromJSON UUID 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser UUID #

parseJSONList :: Value -> Parser [UUID] #

omittedField :: Maybe UUID #

FromJSON Integer 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Integer #

parseJSONList :: Value -> Parser [Integer] #

omittedField :: Maybe Integer #

FromJSON Natural 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Natural #

parseJSONList :: Value -> Parser [Natural] #

omittedField :: Maybe Natural #

FromJSON () 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser () #

parseJSONList :: Value -> Parser [()] #

omittedField :: Maybe () #

FromJSON Bool 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Bool #

parseJSONList :: Value -> Parser [Bool] #

omittedField :: Maybe Bool #

FromJSON Char 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Char #

parseJSONList :: Value -> Parser [Char] #

omittedField :: Maybe Char #

FromJSON Double 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Double #

parseJSONList :: Value -> Parser [Double] #

omittedField :: Maybe Double #

FromJSON Float 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Float #

parseJSONList :: Value -> Parser [Float] #

omittedField :: Maybe Float #

FromJSON Int 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Int #

parseJSONList :: Value -> Parser [Int] #

omittedField :: Maybe Int #

FromJSON Word 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser Word #

parseJSONList :: Value -> Parser [Word] #

omittedField :: Maybe Word #

FromJSON v => FromJSON (KeyMap v) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (KeyMap v) #

parseJSONList :: Value -> Parser [KeyMap v] #

omittedField :: Maybe (KeyMap v) #

FromJSON a => FromJSON (Identity a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Identity a) #

parseJSONList :: Value -> Parser [Identity a] #

omittedField :: Maybe (Identity a) #

FromJSON a => FromJSON (First a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (First a) #

parseJSONList :: Value -> Parser [First a] #

omittedField :: Maybe (First a) #

FromJSON a => FromJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Last a) #

parseJSONList :: Value -> Parser [Last a] #

omittedField :: Maybe (Last a) #

FromJSON a => FromJSON (Down a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Down a) #

parseJSONList :: Value -> Parser [Down a] #

omittedField :: Maybe (Down a) #

FromJSON a => FromJSON (First a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (First a) #

parseJSONList :: Value -> Parser [First a] #

omittedField :: Maybe (First a) #

FromJSON a => FromJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Last a) #

parseJSONList :: Value -> Parser [Last a] #

omittedField :: Maybe (Last a) #

FromJSON a => FromJSON (Max a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Max a) #

parseJSONList :: Value -> Parser [Max a] #

omittedField :: Maybe (Max a) #

FromJSON a => FromJSON (Min a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Min a) #

parseJSONList :: Value -> Parser [Min a] #

omittedField :: Maybe (Min a) #

FromJSON a => FromJSON (WrappedMonoid a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (WrappedMonoid a) #

parseJSONList :: Value -> Parser [WrappedMonoid a] #

omittedField :: Maybe (WrappedMonoid a) #

FromJSON a => FromJSON (Dual a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Dual a) #

parseJSONList :: Value -> Parser [Dual a] #

omittedField :: Maybe (Dual a) #

FromJSON a => FromJSON (NonEmpty a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (NonEmpty a) #

parseJSONList :: Value -> Parser [NonEmpty a] #

omittedField :: Maybe (NonEmpty a) #

(Generic a, GFromJSON Zero (Rep a)) => FromJSON (Generically a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Generically a) #

parseJSONList :: Value -> Parser [Generically a] #

omittedField :: Maybe (Generically a) #

(FromJSON a, Integral a) => FromJSON (Ratio a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Ratio a) #

parseJSONList :: Value -> Parser [Ratio a] #

omittedField :: Maybe (Ratio a) #

FromJSON (Address ByronAddr) 
Instance details

Defined in Cardano.Api.Address

Methods

parseJSON :: Value -> Parser (Address ByronAddr) #

parseJSONList :: Value -> Parser [Address ByronAddr] #

omittedField :: Maybe (Address ByronAddr) #

FromJSON (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

Methods

parseJSON :: Value -> Parser (Address ShelleyAddr) #

parseJSONList :: Value -> Parser [Address ShelleyAddr] #

omittedField :: Maybe (Address ShelleyAddr) #

IsShelleyBasedEra era => FromJSON (AddressInEra era) 
Instance details

Defined in Cardano.Api.Address

Methods

parseJSON :: Value -> Parser (AddressInEra era) #

parseJSONList :: Value -> Parser [AddressInEra era] #

omittedField :: Maybe (AddressInEra era) #

FromJSON (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

Methods

parseJSON :: Value -> Parser (Hash BlockHeader) #

parseJSONList :: Value -> Parser [Hash BlockHeader] #

omittedField :: Maybe (Hash BlockHeader) #

FromJSON (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

parseJSON :: Value -> Parser (Hash DRepKey) #

parseJSONList :: Value -> Parser [Hash DRepKey] #

omittedField :: Maybe (Hash DRepKey) #

FromJSON (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

parseJSON :: Value -> Parser (Hash GenesisKey) #

parseJSONList :: Value -> Parser [Hash GenesisKey] #

omittedField :: Maybe (Hash GenesisKey) #

FromJSON (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

parseJSON :: Value -> Parser (Hash PaymentKey) #

parseJSONList :: Value -> Parser [Hash PaymentKey] #

omittedField :: Maybe (Hash PaymentKey) #

FromJSON (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

parseJSON :: Value -> Parser (Hash StakePoolKey) #

parseJSONList :: Value -> Parser [Hash StakePoolKey] #

omittedField :: Maybe (Hash StakePoolKey) #

FromJSON (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

Methods

parseJSON :: Value -> Parser (Hash ScriptData) #

parseJSONList :: Value -> Parser [Hash ScriptData] #

omittedField :: Maybe (Hash ScriptData) #

FromJSON (VerificationKey PaymentKey) Source # 
Instance details

Defined in Hydra.Cardano.Api.VerificationKey

(IsShelleyBasedEra era, FromJSON (TxOut CtxUTxO era)) => FromJSON (UTxO era) 
Instance details

Defined in Cardano.Api.Query

Methods

parseJSON :: Value -> Parser (UTxO era) #

parseJSONList :: Value -> Parser [UTxO era] #

omittedField :: Maybe (UTxO era) #

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

Defined in Hydra.Cardano.Api.PlutusScript

Methods

parseJSON :: Value -> Parser (PlutusScript lang) #

parseJSONList :: Value -> Parser [PlutusScript lang] #

omittedField :: Maybe (PlutusScript lang) #

IsCardanoEra era => FromJSON (ReferenceScript era) 
Instance details

Defined in Cardano.Api.Script

Methods

parseJSON :: Value -> Parser (ReferenceScript era) #

parseJSONList :: Value -> Parser [ReferenceScript era] #

omittedField :: Maybe (ReferenceScript era) #

SerialiseAsBech32 a => FromJSON (UsingBech32 a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

parseJSON :: Value -> Parser (UsingBech32 a) #

parseJSONList :: Value -> Parser [UsingBech32 a] #

omittedField :: Maybe (UsingBech32 a) #

SerialiseAsRawBytes a => FromJSON (UsingRawBytesHex a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

parseJSON :: Value -> Parser (UsingRawBytesHex a) #

parseJSONList :: Value -> Parser [UsingRawBytesHex a] #

omittedField :: Maybe (UsingRawBytesHex a) #

IsShelleyBasedEra era => FromJSON (TxOutValue era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

parseJSON :: Value -> Parser (TxOutValue era) #

parseJSONList :: Value -> Parser [TxOutValue era] #

omittedField :: Maybe (TxOutValue era) #

Crypto c => FromJSON (ConwayGenesis c) 
Instance details

Defined in Cardano.Ledger.Conway.Genesis

Methods

parseJSON :: Value -> Parser (ConwayGenesis c) #

parseJSONList :: Value -> Parser [ConwayGenesis c] #

omittedField :: Maybe (ConwayGenesis c) #

Era era => FromJSON (Committee era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

parseJSON :: Value -> Parser (Committee era) #

parseJSONList :: Value -> Parser [Committee era] #

omittedField :: Maybe (Committee era) #

FromJSON (UpgradeConwayPParams Identity) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

parseJSON :: Value -> Parser (UpgradeConwayPParams Identity) #

parseJSONList :: Value -> Parser [UpgradeConwayPParams Identity] #

omittedField :: Maybe (UpgradeConwayPParams Identity) #

Crypto c => FromJSON (Delegatee c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

parseJSON :: Value -> Parser (Delegatee c) #

parseJSONList :: Value -> Parser [Delegatee c] #

omittedField :: Maybe (Delegatee c) #

Crypto c => FromJSON (Addr c) 
Instance details

Defined in Cardano.Ledger.Address

Methods

parseJSON :: Value -> Parser (Addr c) #

parseJSONList :: Value -> Parser [Addr c] #

omittedField :: Maybe (Addr c) #

Crypto c => FromJSON (RewardAcnt c) 
Instance details

Defined in Cardano.Ledger.Address

Methods

parseJSON :: Value -> Parser (RewardAcnt c) #

parseJSONList :: Value -> Parser [RewardAcnt c] #

omittedField :: Maybe (RewardAcnt c) #

Crypto c => FromJSON (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser (Anchor c) #

parseJSONList :: Value -> Parser [Anchor c] #

omittedField :: Maybe (Anchor c) #

Crypto c => FromJSON (BlocksMade c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser (BlocksMade c) #

parseJSONList :: Value -> Parser [BlocksMade c] #

omittedField :: Maybe (BlocksMade c) #

FromJSON (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

parseJSON :: Value -> Parser (CompactForm Coin) #

parseJSONList :: Value -> Parser [CompactForm Coin] #

omittedField :: Maybe (CompactForm Coin) #

FromJSON (PParamsHKD Identity era) => FromJSON (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

parseJSON :: Value -> Parser (PParams era) #

parseJSONList :: Value -> Parser [PParams era] #

omittedField :: Maybe (PParams era) #

FromJSON (PParamsHKD StrictMaybe era) => FromJSON (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

parseJSON :: Value -> Parser (PParamsUpdate era) #

parseJSONList :: Value -> Parser [PParamsUpdate era] #

omittedField :: Maybe (PParamsUpdate era) #

Crypto c => FromJSON (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

parseJSON :: Value -> Parser (DRep c) #

parseJSONList :: Value -> Parser [DRep c] #

omittedField :: Maybe (DRep c) #

Crypto c => FromJSON (DRepState c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

parseJSON :: Value -> Parser (DRepState c) #

parseJSONList :: Value -> Parser [DRepState c] #

omittedField :: Maybe (DRepState c) #

Crypto c => FromJSON (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

parseJSON :: Value -> Parser (ScriptHash c) #

parseJSONList :: Value -> Parser [ScriptHash c] #

omittedField :: Maybe (ScriptHash c) #

Crypto c => FromJSON (GenDelegPair c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

parseJSON :: Value -> Parser (GenDelegPair c) #

parseJSONList :: Value -> Parser [GenDelegPair c] #

omittedField :: Maybe (GenDelegPair c) #

Crypto c => FromJSON (GenDelegs c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

parseJSON :: Value -> Parser (GenDelegs c) #

parseJSONList :: Value -> Parser [GenDelegs c] #

omittedField :: Maybe (GenDelegs c) #

FromJSON a => FromJSON (ExUnits' a) 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

parseJSON :: Value -> Parser (ExUnits' a) #

parseJSONList :: Value -> Parser [ExUnits' a] #

omittedField :: Maybe (ExUnits' a) #

Crypto c => FromJSON (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

parseJSON :: Value -> Parser (PoolParams c) #

parseJSONList :: Value -> Parser [PoolParams c] #

omittedField :: Maybe (PoolParams c) #

Crypto c => FromJSON (TxId c) 
Instance details

Defined in Cardano.Ledger.TxIn

Methods

parseJSON :: Value -> Parser (TxId c) #

parseJSONList :: Value -> Parser [TxId c] #

omittedField :: Maybe (TxId c) #

Crypto c => FromJSON (PolicyID c) 
Instance details

Defined in Cardano.Ledger.Mary.Value

Methods

parseJSON :: Value -> Parser (PolicyID c) #

parseJSONList :: Value -> Parser [PolicyID c] #

omittedField :: Maybe (PolicyID c) #

Crypto c => FromJSON (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

parseJSON :: Value -> Parser (ShelleyGenesis c) #

parseJSONList :: Value -> Parser [ShelleyGenesis c] #

omittedField :: Maybe (ShelleyGenesis c) #

Crypto c => FromJSON (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

parseJSON :: Value -> Parser (ShelleyGenesisStaking c) #

parseJSONList :: Value -> Parser [ShelleyGenesisStaking c] #

omittedField :: Maybe (ShelleyGenesisStaking c) #

Era era => FromJSON (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

parseJSON :: Value -> Parser (Constitution era) #

parseJSONList :: Value -> Parser [Constitution era] #

omittedField :: Maybe (Constitution era) #

Crypto c => FromJSON (TransitionConfig (ShelleyEra c)) 
Instance details

Defined in Cardano.Ledger.Shelley.Transition

Methods

parseJSON :: Value -> Parser (TransitionConfig (ShelleyEra c)) #

parseJSONList :: Value -> Parser [TransitionConfig (ShelleyEra c)] #

omittedField :: Maybe (TransitionConfig (ShelleyEra c)) #

FromJSON a => FromJSON (WithOrigin a) 
Instance details

Defined in Cardano.Slotting.Slot

Methods

parseJSON :: Value -> Parser (WithOrigin a) #

parseJSONList :: Value -> Parser [WithOrigin a] #

omittedField :: Maybe (WithOrigin a) #

FromJSON a => FromJSON (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Methods

parseJSON :: Value -> Parser (StrictMaybe a) #

parseJSONList :: Value -> Parser [StrictMaybe a] #

omittedField :: Maybe (StrictMaybe a) #

FromJSON a => FromJSON (StrictSeq a) 
Instance details

Defined in Data.Sequence.Strict

Methods

parseJSON :: Value -> Parser (StrictSeq a) #

parseJSONList :: Value -> Parser [StrictSeq a] #

omittedField :: Maybe (StrictSeq a) #

FromJSON a => FromJSON (IntMap a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (IntMap a) #

parseJSONList :: Value -> Parser [IntMap a] #

omittedField :: Maybe (IntMap a) #

FromJSON a => FromJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Seq a) #

parseJSONList :: Value -> Parser [Seq a] #

omittedField :: Maybe (Seq a) #

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

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Set a) #

parseJSONList :: Value -> Parser [Set a] #

omittedField :: Maybe (Set a) #

FromJSON v => FromJSON (Tree v) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Tree v) #

parseJSONList :: Value -> Parser [Tree v] #

omittedField :: Maybe (Tree v) #

FromJSON1 f => FromJSON (Fix f) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Fix f) #

parseJSONList :: Value -> Parser [Fix f] #

omittedField :: Maybe (Fix f) #

(FromJSON1 f, Functor f) => FromJSON (Mu f) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Mu f) #

parseJSONList :: Value -> Parser [Mu f] #

omittedField :: Maybe (Mu f) #

(FromJSON1 f, Functor f) => FromJSON (Nu f) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Nu f) #

parseJSONList :: Value -> Parser [Nu f] #

omittedField :: Maybe (Nu f) #

FromJSON a => FromJSON (DNonEmpty a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (DNonEmpty a) #

parseJSONList :: Value -> Parser [DNonEmpty a] #

omittedField :: Maybe (DNonEmpty a) #

FromJSON a => FromJSON (DList a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (DList a) #

parseJSONList :: Value -> Parser [DList a] #

omittedField :: Maybe (DList a) #

FromJSON out => FromJSON (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

parseJSON :: Value -> Parser (UTxO' out) #

parseJSONList :: Value -> Parser [UTxO' out] #

omittedField :: Maybe (UTxO' out) #

FromJSON a => FromJSON (Array a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Array a) #

parseJSONList :: Value -> Parser [Array a] #

omittedField :: Maybe (Array a) #

(Prim a, FromJSON a) => FromJSON (PrimArray a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (PrimArray a) #

parseJSONList :: Value -> Parser [PrimArray a] #

omittedField :: Maybe (PrimArray a) #

FromJSON a => FromJSON (SmallArray a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (SmallArray a) #

parseJSONList :: Value -> Parser [SmallArray a] #

omittedField :: Maybe (SmallArray a) #

FromJSON a => FromJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Maybe a) #

parseJSONList :: Value -> Parser [Maybe a] #

omittedField :: Maybe0 (Maybe a) #

(Eq a, Hashable a, FromJSON a) => FromJSON (HashSet a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (HashSet a) #

parseJSONList :: Value -> Parser [HashSet a] #

omittedField :: Maybe (HashSet a) #

FromJSON a => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Vector a) #

parseJSONList :: Value -> Parser [Vector a] #

omittedField :: Maybe (Vector a) #

(Prim a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Vector a) #

parseJSONList :: Value -> Parser [Vector a] #

omittedField :: Maybe (Vector a) #

(Storable a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Vector a) #

parseJSONList :: Value -> Parser [Vector a] #

omittedField :: Maybe (Vector a) #

(Vector Vector a, FromJSON a) => FromJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Vector a) #

parseJSONList :: Value -> Parser [Vector a] #

omittedField :: Maybe (Vector a) #

FromJSON a => FromJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Maybe a) #

parseJSONList :: Value -> Parser [Maybe a] #

omittedField :: Maybe (Maybe a) #

FromJSON a => FromJSON (a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a) #

parseJSONList :: Value -> Parser [(a)] #

omittedField :: Maybe (a) #

FromJSON a => FromJSON [a] 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser [a] #

parseJSONList :: Value -> Parser [[a]] #

omittedField :: Maybe [a] #

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

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Either a b) #

parseJSONList :: Value -> Parser [Either a b] #

omittedField :: Maybe (Either a b) #

HasResolution a => FromJSON (Fixed a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Fixed a) #

parseJSONList :: Value -> Parser [Fixed a] #

omittedField :: Maybe (Fixed a) #

FromJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Proxy a) #

parseJSONList :: Value -> Parser [Proxy a] #

omittedField :: Maybe (Proxy a) #

FromJSON (File content direction) 
Instance details

Defined in Cardano.Api.IO.Base

Methods

parseJSON :: Value -> Parser (File content direction) #

parseJSONList :: Value -> Parser [File content direction] #

omittedField :: Maybe (File content direction) #

IsShelleyBasedEra era => FromJSON (TxOut CtxTx era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

parseJSON :: Value -> Parser (TxOut CtxTx era) #

parseJSONList :: Value -> Parser [TxOut CtxTx era] #

omittedField :: Maybe (TxOut CtxTx era) #

IsShelleyBasedEra era => FromJSON (TxOut CtxUTxO era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

parseJSON :: Value -> Parser (TxOut CtxUTxO era) #

parseJSONList :: Value -> Parser [TxOut CtxUTxO era] #

omittedField :: Maybe (TxOut CtxUTxO era) #

HashAlgorithm h => FromJSON (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

parseJSON :: Value -> Parser (Hash h a) #

parseJSONList :: Value -> Parser [Hash h a] #

omittedField :: Maybe (Hash h a) #

(FromJSON v, FromJSON k, FromJSONKey k) => FromJSON (ListMap k v) 
Instance details

Defined in Data.ListMap

Methods

parseJSON :: Value -> Parser (ListMap k v) #

parseJSONList :: Value -> Parser [ListMap k v] #

omittedField :: Maybe (ListMap k v) #

FromJSON (AlonzoPParams Identity era) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Methods

parseJSON :: Value -> Parser (AlonzoPParams Identity era) #

parseJSONList :: Value -> Parser [AlonzoPParams Identity era] #

omittedField :: Maybe (AlonzoPParams Identity era) #

FromJSON (BabbagePParams Identity era) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Methods

parseJSON :: Value -> Parser (BabbagePParams Identity era) #

parseJSONList :: Value -> Parser [BabbagePParams Identity era] #

omittedField :: Maybe (BabbagePParams Identity era) #

FromJSON b => FromJSON (Annotated b ()) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

parseJSON :: Value -> Parser (Annotated b ()) #

parseJSONList :: Value -> Parser [Annotated b ()] #

omittedField :: Maybe (Annotated b ()) #

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

Defined in Cardano.Ledger.Conway.PParams

Methods

parseJSON :: Value -> Parser (ConwayPParams Identity era) #

parseJSONList :: Value -> Parser [ConwayPParams Identity era] #

omittedField :: Maybe (ConwayPParams Identity era) #

Bounded (BoundedRatio b Word64) => FromJSON (BoundedRatio b Word64) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

parseJSON :: Value -> Parser (BoundedRatio b Word64) #

parseJSONList :: Value -> Parser [BoundedRatio b Word64] #

omittedField :: Maybe (BoundedRatio b Word64) #

Crypto c => FromJSON (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

parseJSON :: Value -> Parser (Credential kr c) #

parseJSONList :: Value -> Parser [Credential kr c] #

omittedField :: Maybe (Credential kr c) #

Crypto c => FromJSON (KeyHash disc c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

parseJSON :: Value -> Parser (KeyHash disc c) #

parseJSONList :: Value -> Parser [KeyHash disc c] #

omittedField :: Maybe (KeyHash disc c) #

Crypto c => FromJSON (SafeHash c index) 
Instance details

Defined in Cardano.Ledger.SafeHash

Methods

parseJSON :: Value -> Parser (SafeHash c index) #

parseJSONList :: Value -> Parser [SafeHash c index] #

omittedField :: Maybe (SafeHash c index) #

FromJSON (ShelleyPParams Identity era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

parseJSON :: Value -> Parser (ShelleyPParams Identity era) #

parseJSONList :: Value -> Parser [ShelleyPParams Identity era] #

omittedField :: Maybe (ShelleyPParams Identity era) #

(FromJSONKey k, Ord k, FromJSON v) => FromJSON (Map k v) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Map k v) #

parseJSONList :: Value -> Parser [Map k v] #

omittedField :: Maybe (Map k v) #

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

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Either a b) #

parseJSONList :: Value -> Parser [Either a b] #

omittedField :: Maybe (Either a b) #

(FromJSON a, FromJSON b) => FromJSON (These a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (These a b) #

parseJSONList :: Value -> Parser [These a b] #

omittedField :: Maybe (These a b) #

(FromJSON a, FromJSON b) => FromJSON (Pair a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Pair a b) #

parseJSONList :: Value -> Parser [Pair a b] #

omittedField :: Maybe (Pair a b) #

(FromJSON a, FromJSON b) => FromJSON (These a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (These a b) #

parseJSONList :: Value -> Parser [These a b] #

omittedField :: Maybe (These a b) #

(FromJSON v, FromJSONKey k, Eq k, Hashable k) => FromJSON (HashMap k v) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (HashMap k v) #

parseJSONList :: Value -> Parser [HashMap k v] #

omittedField :: Maybe (HashMap k v) #

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

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b) #

parseJSONList :: Value -> Parser [(a, b)] #

omittedField :: Maybe (a, b) #

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

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Const a b) #

parseJSONList :: Value -> Parser [Const a b] #

omittedField :: Maybe (Const a b) #

(Typeable t, FromJSON a) => FromJSON (THKD t Identity a) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

parseJSON :: Value -> Parser (THKD t Identity a) #

parseJSONList :: Value -> Parser [THKD t Identity a] #

omittedField :: Maybe (THKD t Identity a) #

(Typeable t, FromJSON a) => FromJSON (THKD t StrictMaybe a) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

parseJSON :: Value -> Parser (THKD t StrictMaybe a) #

parseJSONList :: Value -> Parser [THKD t StrictMaybe a] #

omittedField :: Maybe (THKD t StrictMaybe a) #

FromJSON b => FromJSON (Tagged a b) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Tagged a b) #

parseJSONList :: Value -> Parser [Tagged a b] #

omittedField :: Maybe (Tagged a b) #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (These1 f g a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (These1 f g a) #

parseJSONList :: Value -> Parser [These1 f g a] #

omittedField :: Maybe (These1 f g a) #

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

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c) #

parseJSONList :: Value -> Parser [(a, b, c)] #

omittedField :: Maybe (a, b, c) #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Product f g a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Product f g a) #

parseJSONList :: Value -> Parser [Product f g a] #

omittedField :: Maybe (Product f g a) #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Sum f g a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Sum f g a) #

parseJSONList :: Value -> Parser [Sum f g a] #

omittedField :: Maybe (Sum f g a) #

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

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d) #

parseJSONList :: Value -> Parser [(a, b, c, d)] #

omittedField :: Maybe (a, b, c, d) #

(FromJSON1 f, FromJSON1 g, FromJSON a) => FromJSON (Compose f g a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (Compose f g a) #

parseJSONList :: Value -> Parser [Compose f g a] #

omittedField :: Maybe (Compose f g a) #

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

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e) #

parseJSONList :: Value -> Parser [(a, b, c, d, e)] #

omittedField :: Maybe (a, b, c, d, e) #

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

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f)] #

omittedField :: Maybe (a, b, c, d, e, f) #

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

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g)] #

omittedField :: Maybe (a, b, c, d, e, f, g) #

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

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i) => FromJSON (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j) => FromJSON (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k) => FromJSON (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k, l) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n) #

(FromJSON a, FromJSON b, FromJSON c, FromJSON d, FromJSON e, FromJSON f, FromJSON g, FromJSON h, FromJSON i, FromJSON j, FromJSON k, FromJSON l, FromJSON m, FromJSON n, FromJSON o) => FromJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

parseJSON :: Value -> Parser (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

parseJSONList :: Value -> Parser [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] #

omittedField :: Maybe (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) #

class ToJSON a #

Instances

Instances details
ToJSON Key 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Key -> Value #

toEncoding :: Key -> Encoding #

toJSONList :: [Key] -> Value #

toEncodingList :: [Key] -> Encoding #

omitField :: Key -> Bool #

ToJSON DotNetTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DotNetTime -> Value #

toEncoding :: DotNetTime -> Encoding #

toJSONList :: [DotNetTime] -> Value #

toEncodingList :: [DotNetTime] -> Encoding #

omitField :: DotNetTime -> Bool #

ToJSON Value 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Value -> Value #

toEncoding :: Value -> Encoding #

toJSONList :: [Value] -> Value #

toEncodingList :: [Value] -> Encoding #

omitField :: Value -> Bool #

ToJSON Version 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Version -> Value #

toEncoding :: Version -> Encoding #

toJSONList :: [Version] -> Value #

toEncodingList :: [Version] -> Encoding #

omitField :: Version -> Bool #

ToJSON CTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: CTime -> Value #

toEncoding :: CTime -> Encoding #

toJSONList :: [CTime] -> Value #

toEncodingList :: [CTime] -> Encoding #

omitField :: CTime -> Bool #

ToJSON Void 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Void -> Value #

toEncoding :: Void -> Encoding #

toJSONList :: [Void] -> Value #

toEncodingList :: [Void] -> Encoding #

omitField :: Void -> Bool #

ToJSON Int16 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int16 -> Value #

toEncoding :: Int16 -> Encoding #

toJSONList :: [Int16] -> Value #

toEncodingList :: [Int16] -> Encoding #

omitField :: Int16 -> Bool #

ToJSON Int32 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int32 -> Value #

toEncoding :: Int32 -> Encoding #

toJSONList :: [Int32] -> Value #

toEncodingList :: [Int32] -> Encoding #

omitField :: Int32 -> Bool #

ToJSON Int64 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int64 -> Value #

toEncoding :: Int64 -> Encoding #

toJSONList :: [Int64] -> Value #

toEncodingList :: [Int64] -> Encoding #

omitField :: Int64 -> Bool #

ToJSON Int8 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int8 -> Value #

toEncoding :: Int8 -> Encoding #

toJSONList :: [Int8] -> Value #

toEncodingList :: [Int8] -> Encoding #

omitField :: Int8 -> Bool #

ToJSON Word16 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word16 -> Value #

toEncoding :: Word16 -> Encoding #

toJSONList :: [Word16] -> Value #

toEncodingList :: [Word16] -> Encoding #

omitField :: Word16 -> Bool #

ToJSON Word32 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word32 -> Value #

toEncoding :: Word32 -> Encoding #

toJSONList :: [Word32] -> Value #

toEncodingList :: [Word32] -> Encoding #

omitField :: Word32 -> Bool #

ToJSON Word64 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word64 -> Value #

toEncoding :: Word64 -> Encoding #

toJSONList :: [Word64] -> Value #

toEncodingList :: [Word64] -> Encoding #

omitField :: Word64 -> Bool #

ToJSON Word8 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word8 -> Value #

toEncoding :: Word8 -> Encoding #

toJSONList :: [Word8] -> Value #

toEncodingList :: [Word8] -> Encoding #

omitField :: Word8 -> Bool #

ToJSON StakeAddress 
Instance details

Defined in Cardano.Api.Address

Methods

toJSON :: StakeAddress -> Value #

toEncoding :: StakeAddress -> Encoding #

toJSONList :: [StakeAddress] -> Value #

toEncodingList :: [StakeAddress] -> Encoding #

omitField :: StakeAddress -> Bool #

ToJSON StakeCredential 
Instance details

Defined in Cardano.Api.Address

ToJSON ChainPoint 
Instance details

Defined in Cardano.Api.Block

Methods

toJSON :: ChainPoint -> Value #

toEncoding :: ChainPoint -> Encoding #

toJSONList :: [ChainPoint] -> Value #

toEncodingList :: [ChainPoint] -> Encoding #

omitField :: ChainPoint -> Bool #

ToJSON ChainTip 
Instance details

Defined in Cardano.Api.Block

Methods

toJSON :: ChainTip -> Value #

toEncoding :: ChainTip -> Encoding #

toJSONList :: [ChainTip] -> Value #

toEncodingList :: [ChainTip] -> Encoding #

omitField :: ChainTip -> Bool #

ToJSON AnyShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

ToJSON AnyCardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

toJSON :: AnyCardanoEra -> Value #

toEncoding :: AnyCardanoEra -> Encoding #

toJSONList :: [AnyCardanoEra] -> Value #

toEncodingList :: [AnyCardanoEra] -> Encoding #

omitField :: AnyCardanoEra -> Bool #

ToJSON LocalTxMonitoringResult 
Instance details

Defined in Cardano.Api.IPC

ToJSON TxValidationErrorInCardanoMode 
Instance details

Defined in Cardano.Api.InMode

ToJSON NetworkId Source # 
Instance details

Defined in Hydra.Cardano.Api.NetworkId

Methods

toJSON :: NetworkId -> Value #

toEncoding :: NetworkId -> Encoding #

toJSONList :: [NetworkId] -> Value #

toEncodingList :: [NetworkId] -> Encoding #

omitField :: NetworkId -> Bool #

ToJSON CostModels 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toJSON :: CostModels -> Value #

toEncoding :: CostModels -> Encoding #

toJSONList :: [CostModels] -> Value #

toEncodingList :: [CostModels] -> Encoding #

omitField :: CostModels -> Bool #

ToJSON ExecutionUnitPrices 
Instance details

Defined in Cardano.Api.ProtocolParameters

ToJSON PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toJSON :: PraosNonce -> Value #

toEncoding :: PraosNonce -> Encoding #

toJSONList :: [PraosNonce] -> Value #

toEncodingList :: [PraosNonce] -> Encoding #

omitField :: PraosNonce -> Bool #

ToJSON ProtocolParameters 
Instance details

Defined in Cardano.Api.ProtocolParameters

ToJSON DelegationsAndRewards 
Instance details

Defined in Cardano.Api.Rewards

ToJSON AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

ToJSON ExecutionUnits 
Instance details

Defined in Cardano.Api.Script

ToJSON ScriptHash 
Instance details

Defined in Cardano.Api.Script

Methods

toJSON :: ScriptHash -> Value #

toEncoding :: ScriptHash -> Encoding #

toJSONList :: [ScriptHash] -> Value #

toEncodingList :: [ScriptHash] -> Encoding #

omitField :: ScriptHash -> Bool #

ToJSON ScriptInAnyLang 
Instance details

Defined in Cardano.Api.Script

ToJSON SimpleScript 
Instance details

Defined in Cardano.Api.Script

Methods

toJSON :: SimpleScript -> Value #

toEncoding :: SimpleScript -> Encoding #

toJSONList :: [SimpleScript] -> Value #

toEncodingList :: [SimpleScript] -> Encoding #

omitField :: SimpleScript -> Bool #

ToJSON HashableScriptData Source # 
Instance details

Defined in Hydra.Cardano.Api.ScriptData

ToJSON ScriptData Source # 
Instance details

Defined in Hydra.Cardano.Api.ScriptData

Methods

toJSON :: ScriptData -> Value #

toEncoding :: ScriptData -> Encoding #

toJSONList :: [ScriptData] -> Value #

toEncodingList :: [ScriptData] -> Encoding #

omitField :: ScriptData -> Bool #

ToJSON TextEnvelopeCddl 
Instance details

Defined in Cardano.Api.SerialiseLedgerCddl

ToJSON TextEnvelope 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Methods

toJSON :: TextEnvelope -> Value #

toEncoding :: TextEnvelope -> Encoding #

toJSONList :: [TextEnvelope] -> Value #

toEncodingList :: [TextEnvelope] -> Encoding #

omitField :: TextEnvelope -> Bool #

ToJSON TextEnvelopeDescr 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

ToJSON TextEnvelopeType 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

ToJSON ScriptWitnessIndex 
Instance details

Defined in Cardano.Api.Tx.Body

ToJSON TxId 
Instance details

Defined in Cardano.Api.TxIn

Methods

toJSON :: TxId -> Value #

toEncoding :: TxId -> Encoding #

toJSONList :: [TxId] -> Value #

toEncodingList :: [TxId] -> Encoding #

omitField :: TxId -> Bool #

ToJSON TxIn 
Instance details

Defined in Cardano.Api.TxIn

Methods

toJSON :: TxIn -> Value #

toEncoding :: TxIn -> Encoding #

toJSONList :: [TxIn] -> Value #

toEncodingList :: [TxIn] -> Encoding #

omitField :: TxIn -> Bool #

ToJSON TxIx 
Instance details

Defined in Cardano.Api.TxIn

Methods

toJSON :: TxIx -> Value #

toEncoding :: TxIx -> Encoding #

toJSONList :: [TxIx] -> Value #

toEncodingList :: [TxIx] -> Encoding #

omitField :: TxIx -> Bool #

ToJSON AssetName 
Instance details

Defined in Cardano.Api.Value

Methods

toJSON :: AssetName -> Value #

toEncoding :: AssetName -> Encoding #

toJSONList :: [AssetName] -> Value #

toEncodingList :: [AssetName] -> Encoding #

omitField :: AssetName -> Bool #

ToJSON PolicyId 
Instance details

Defined in Cardano.Api.Value

Methods

toJSON :: PolicyId -> Value #

toEncoding :: PolicyId -> Encoding #

toJSONList :: [PolicyId] -> Value #

toEncodingList :: [PolicyId] -> Encoding #

omitField :: PolicyId -> Bool #

ToJSON Quantity 
Instance details

Defined in Cardano.Api.Value

Methods

toJSON :: Quantity -> Value #

toEncoding :: Quantity -> Encoding #

toJSONList :: [Quantity] -> Value #

toEncodingList :: [Quantity] -> Encoding #

omitField :: Quantity -> Bool #

ToJSON Value 
Instance details

Defined in Cardano.Api.Value

Methods

toJSON :: Value -> Value0 #

toEncoding :: Value -> Encoding #

toJSONList :: [Value] -> Value0 #

toEncodingList :: [Value] -> Encoding #

omitField :: Value -> Bool #

ToJSON ValueNestedRep 
Instance details

Defined in Cardano.Api.Value

ToJSON ProtocolMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Methods

toJSON :: ProtocolMagic -> Value #

toEncoding :: ProtocolMagic -> Encoding #

toJSONList :: [ProtocolMagic] -> Value #

toEncodingList :: [ProtocolMagic] -> Encoding #

omitField :: ProtocolMagic -> Bool #

ToJSON ProtocolMagicId 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Methods

toJSON :: ProtocolMagicId -> Value #

toEncoding :: ProtocolMagicId -> Encoding #

toJSONList :: [ProtocolMagicId] -> Value #

toEncodingList :: [ProtocolMagicId] -> Encoding #

omitField :: ProtocolMagicId -> Bool #

ToJSON RequiresNetworkMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Methods

toJSON :: RequiresNetworkMagic -> Value #

toEncoding :: RequiresNetworkMagic -> Encoding #

toJSONList :: [RequiresNetworkMagic] -> Value #

toEncodingList :: [RequiresNetworkMagic] -> Encoding #

omitField :: RequiresNetworkMagic -> Bool #

ToJSON RedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.VerificationKey

Methods

toJSON :: RedeemVerificationKey -> Value #

toEncoding :: RedeemVerificationKey -> Encoding #

toJSONList :: [RedeemVerificationKey] -> Value #

toEncodingList :: [RedeemVerificationKey] -> Encoding #

omitField :: RedeemVerificationKey -> Bool #

ToJSON VerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

Methods

toJSON :: VerificationKey -> Value #

toEncoding :: VerificationKey -> Encoding #

toJSONList :: [VerificationKey] -> Value #

toEncodingList :: [VerificationKey] -> Encoding #

omitField :: VerificationKey -> Bool #

ToJSON AlonzoGenesis 
Instance details

Defined in Cardano.Ledger.Alonzo.Genesis

Methods

toJSON :: AlonzoGenesis -> Value #

toEncoding :: AlonzoGenesis -> Encoding #

toJSONList :: [AlonzoGenesis] -> Value #

toEncodingList :: [AlonzoGenesis] -> Encoding #

omitField :: AlonzoGenesis -> Bool #

ToJSON CoinPerWord 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Methods

toJSON :: CoinPerWord -> Value #

toEncoding :: CoinPerWord -> Encoding #

toJSONList :: [CoinPerWord] -> Value #

toEncodingList :: [CoinPerWord] -> Encoding #

omitField :: CoinPerWord -> Bool #

ToJSON OrdExUnits 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Methods

toJSON :: OrdExUnits -> Value #

toEncoding :: OrdExUnits -> Encoding #

toJSONList :: [OrdExUnits] -> Value #

toEncodingList :: [OrdExUnits] -> Encoding #

omitField :: OrdExUnits -> Bool #

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 #

ToJSON NextEpochChange 
Instance details

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

Methods

toJSON :: NextEpochChange -> Value #

toEncoding :: NextEpochChange -> Encoding #

toJSONList :: [NextEpochChange] -> Value #

toEncodingList :: [NextEpochChange] -> Encoding #

omitField :: NextEpochChange -> Bool #

ToJSON CoinPerByte 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Methods

toJSON :: CoinPerByte -> Value #

toEncoding :: CoinPerByte -> Encoding #

toJSONList :: [CoinPerByte] -> Value #

toEncodingList :: [CoinPerByte] -> Encoding #

omitField :: CoinPerByte -> Bool #

ToJSON ByteSpan 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

toJSON :: ByteSpan -> Value #

toEncoding :: ByteSpan -> Encoding #

toJSONList :: [ByteSpan] -> Value #

toEncodingList :: [ByteSpan] -> Encoding #

omitField :: ByteSpan -> Bool #

ToJSON Version 
Instance details

Defined in Cardano.Ledger.Binary.Version

Methods

toJSON :: Version -> Value #

toEncoding :: Version -> Encoding #

toJSONList :: [Version] -> Value #

toEncodingList :: [Version] -> Encoding #

omitField :: Version -> Bool #

ToJSON AddrAttributes 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

Methods

toJSON :: AddrAttributes -> Value #

toEncoding :: AddrAttributes -> Encoding #

toJSONList :: [AddrAttributes] -> Value #

toEncodingList :: [AddrAttributes] -> Encoding #

omitField :: AddrAttributes -> Bool #

ToJSON HDAddressPayload 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

Methods

toJSON :: HDAddressPayload -> Value #

toEncoding :: HDAddressPayload -> Encoding #

toJSONList :: [HDAddressPayload] -> Value #

toEncodingList :: [HDAddressPayload] -> Encoding #

omitField :: HDAddressPayload -> Bool #

ToJSON AddrType 
Instance details

Defined in Cardano.Chain.Common.AddrSpendingData

Methods

toJSON :: AddrType -> Value #

toEncoding :: AddrType -> Encoding #

toJSONList :: [AddrType] -> Value #

toEncodingList :: [AddrType] -> Encoding #

omitField :: AddrType -> Bool #

ToJSON Address 
Instance details

Defined in Cardano.Chain.Common.Address

Methods

toJSON :: Address -> Value #

toEncoding :: Address -> Encoding #

toJSONList :: [Address] -> Value #

toEncodingList :: [Address] -> Encoding #

omitField :: Address -> Bool #

ToJSON NetworkMagic 
Instance details

Defined in Cardano.Chain.Common.NetworkMagic

Methods

toJSON :: NetworkMagic -> Value #

toEncoding :: NetworkMagic -> Encoding #

toJSONList :: [NetworkMagic] -> Value #

toEncodingList :: [NetworkMagic] -> Encoding #

omitField :: NetworkMagic -> Bool #

ToJSON Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

toJSON :: Tx -> Value #

toEncoding :: Tx -> Encoding #

toJSONList :: [Tx] -> Value #

toEncodingList :: [Tx] -> Encoding #

omitField :: Tx -> Bool #

ToJSON TxIn 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

toJSON :: TxIn -> Value #

toEncoding :: TxIn -> Encoding #

toJSONList :: [TxIn] -> Value #

toEncodingList :: [TxIn] -> Encoding #

omitField :: TxIn -> Bool #

ToJSON TxOut 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

toJSON :: TxOut -> Value #

toEncoding :: TxOut -> Encoding #

toJSONList :: [TxOut] -> Value #

toEncodingList :: [TxOut] -> Encoding #

omitField :: TxOut -> Bool #

ToJSON TxInWitness 
Instance details

Defined in Cardano.Chain.UTxO.TxWitness

Methods

toJSON :: TxInWitness -> Value #

toEncoding :: TxInWitness -> Encoding #

toJSONList :: [TxInWitness] -> Value #

toEncodingList :: [TxInWitness] -> Encoding #

omitField :: TxInWitness -> Bool #

ToJSON TxSigData 
Instance details

Defined in Cardano.Chain.UTxO.TxWitness

Methods

toJSON :: TxSigData -> Value #

toEncoding :: TxSigData -> Encoding #

toJSONList :: [TxSigData] -> Value #

toEncodingList :: [TxSigData] -> Encoding #

omitField :: TxSigData -> Bool #

ToJSON ProtocolVersion 
Instance details

Defined in Cardano.Chain.Update.ProtocolVersion

Methods

toJSON :: ProtocolVersion -> Value #

toEncoding :: ProtocolVersion -> Encoding #

toJSONList :: [ProtocolVersion] -> Value #

toEncodingList :: [ProtocolVersion] -> Encoding #

omitField :: ProtocolVersion -> Bool #

ToJSON GovActionIx 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: GovActionIx -> Value #

toEncoding :: GovActionIx -> Encoding #

toJSONList :: [GovActionIx] -> Value #

toEncodingList :: [GovActionIx] -> Encoding #

omitField :: GovActionIx -> Bool #

ToJSON Vote 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: Vote -> Value #

toEncoding :: Vote -> Encoding #

toJSONList :: [Vote] -> Value #

toEncodingList :: [Vote] -> Encoding #

omitField :: Vote -> Bool #

ToJSON DRepVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

toJSON :: DRepVotingThresholds -> Value #

toEncoding :: DRepVotingThresholds -> Encoding #

toJSONList :: [DRepVotingThresholds] -> Value #

toEncodingList :: [DRepVotingThresholds] -> Encoding #

omitField :: DRepVotingThresholds -> Bool #

ToJSON PoolVotingThresholds 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

toJSON :: PoolVotingThresholds -> Value #

toEncoding :: PoolVotingThresholds -> Encoding #

toJSONList :: [PoolVotingThresholds] -> Value #

toEncodingList :: [PoolVotingThresholds] -> Encoding #

omitField :: PoolVotingThresholds -> Bool #

ToJSON CertIx 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: CertIx -> Value #

toEncoding :: CertIx -> Encoding #

toJSONList :: [CertIx] -> Value #

toEncodingList :: [CertIx] -> Encoding #

omitField :: CertIx -> Bool #

ToJSON DnsName 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: DnsName -> Value #

toEncoding :: DnsName -> Encoding #

toJSONList :: [DnsName] -> Value #

toEncodingList :: [DnsName] -> Encoding #

omitField :: DnsName -> Bool #

ToJSON EpochInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: EpochInterval -> Value #

toEncoding :: EpochInterval -> Encoding #

toJSONList :: [EpochInterval] -> Value #

toEncodingList :: [EpochInterval] -> Encoding #

omitField :: EpochInterval -> Bool #

ToJSON Network 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Network -> Value #

toEncoding :: Network -> Encoding #

toJSONList :: [Network] -> Value #

toEncodingList :: [Network] -> Encoding #

omitField :: Network -> Bool #

ToJSON NonNegativeInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: NonNegativeInterval -> Value #

toEncoding :: NonNegativeInterval -> Encoding #

toJSONList :: [NonNegativeInterval] -> Value #

toEncodingList :: [NonNegativeInterval] -> Encoding #

omitField :: NonNegativeInterval -> Bool #

ToJSON Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Nonce -> Value #

toEncoding :: Nonce -> Encoding #

toJSONList :: [Nonce] -> Value #

toEncodingList :: [Nonce] -> Encoding #

omitField :: Nonce -> Bool #

ToJSON Port 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Port -> Value #

toEncoding :: Port -> Encoding #

toJSONList :: [Port] -> Value #

toEncodingList :: [Port] -> Encoding #

omitField :: Port -> Bool #

ToJSON PositiveInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: PositiveInterval -> Value #

toEncoding :: PositiveInterval -> Encoding #

toJSONList :: [PositiveInterval] -> Value #

toEncodingList :: [PositiveInterval] -> Encoding #

omitField :: PositiveInterval -> Bool #

ToJSON PositiveUnitInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: PositiveUnitInterval -> Value #

toEncoding :: PositiveUnitInterval -> Encoding #

toJSONList :: [PositiveUnitInterval] -> Value #

toEncodingList :: [PositiveUnitInterval] -> Encoding #

omitField :: PositiveUnitInterval -> Bool #

ToJSON ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: ProtVer -> Value #

toEncoding :: ProtVer -> Encoding #

toJSONList :: [ProtVer] -> Value #

toEncodingList :: [ProtVer] -> Encoding #

omitField :: ProtVer -> Bool #

ToJSON TxIx 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: TxIx -> Value #

toEncoding :: TxIx -> Encoding #

toJSONList :: [TxIx] -> Value #

toEncodingList :: [TxIx] -> Encoding #

omitField :: TxIx -> Bool #

ToJSON UnitInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: UnitInterval -> Value #

toEncoding :: UnitInterval -> Encoding #

toJSONList :: [UnitInterval] -> Value #

toEncodingList :: [UnitInterval] -> Encoding #

omitField :: UnitInterval -> Bool #

ToJSON Url 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Url -> Value #

toEncoding :: Url -> Encoding #

toJSONList :: [Url] -> Value #

toEncodingList :: [Url] -> Encoding #

omitField :: Url -> Bool #

ToJSON Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toJSON :: Coin -> Value #

toEncoding :: Coin -> Encoding #

toJSONList :: [Coin] -> Value #

toEncodingList :: [Coin] -> Encoding #

omitField :: Coin -> Bool #

ToJSON DeltaCoin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toJSON :: DeltaCoin -> Value #

toEncoding :: DeltaCoin -> Encoding #

toJSONList :: [DeltaCoin] -> Value #

toEncodingList :: [DeltaCoin] -> Encoding #

omitField :: DeltaCoin -> Bool #

ToJSON Ptr 
Instance details

Defined in Cardano.Ledger.Credential

Methods

toJSON :: Ptr -> Value #

toEncoding :: Ptr -> Encoding #

toJSONList :: [Ptr] -> Value #

toEncodingList :: [Ptr] -> Encoding #

omitField :: Ptr -> Bool #

ToJSON CostModel 
Instance details

Defined in Cardano.Ledger.Plutus.CostModels

Methods

toJSON :: CostModel -> Value #

toEncoding :: CostModel -> Encoding #

toJSONList :: [CostModel] -> Value #

toEncodingList :: [CostModel] -> Encoding #

omitField :: CostModel -> Bool #

ToJSON CostModelError 
Instance details

Defined in Cardano.Ledger.Plutus.CostModels

Methods

toJSON :: CostModelError -> Value #

toEncoding :: CostModelError -> Encoding #

toJSONList :: [CostModelError] -> Value #

toEncodingList :: [CostModelError] -> Encoding #

omitField :: CostModelError -> Bool #

ToJSON CostModels 
Instance details

Defined in Cardano.Ledger.Plutus.CostModels

Methods

toJSON :: CostModels -> Value #

toEncoding :: CostModels -> Encoding #

toJSONList :: [CostModels] -> Value #

toEncodingList :: [CostModels] -> Encoding #

omitField :: CostModels -> Bool #

ToJSON ExUnits 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

toJSON :: ExUnits -> Value #

toEncoding :: ExUnits -> Encoding #

toJSONList :: [ExUnits] -> Value #

toEncodingList :: [ExUnits] -> Encoding #

omitField :: ExUnits -> Bool #

ToJSON Prices 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

toJSON :: Prices -> Value #

toEncoding :: Prices -> Encoding #

toJSONList :: [Prices] -> Value #

toEncodingList :: [Prices] -> Encoding #

omitField :: Prices -> Bool #

ToJSON Language 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

toJSON :: Language -> Value #

toEncoding :: Language -> Encoding #

toJSONList :: [Language] -> Value #

toEncodingList :: [Language] -> Encoding #

omitField :: Language -> Bool #

ToJSON PoolMetadata 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

toJSON :: PoolMetadata -> Value #

toEncoding :: PoolMetadata -> Encoding #

toJSONList :: [PoolMetadata] -> Value #

toEncodingList :: [PoolMetadata] -> Encoding #

omitField :: PoolMetadata -> Bool #

ToJSON StakePoolRelay 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

toJSON :: StakePoolRelay -> Value #

toEncoding :: StakePoolRelay -> Encoding #

toJSONList :: [StakePoolRelay] -> Value #

toEncodingList :: [StakePoolRelay] -> Encoding #

omitField :: StakePoolRelay -> Bool #

ToJSON AssetName 
Instance details

Defined in Cardano.Ledger.Mary.Value

Methods

toJSON :: AssetName -> Value #

toEncoding :: AssetName -> Encoding #

toJSONList :: [AssetName] -> Value #

toEncodingList :: [AssetName] -> Encoding #

omitField :: AssetName -> Bool #

ToJSON NominalDiffTimeMicro 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toJSON :: NominalDiffTimeMicro -> Value #

toEncoding :: NominalDiffTimeMicro -> Encoding #

toJSONList :: [NominalDiffTimeMicro] -> Value #

toEncodingList :: [NominalDiffTimeMicro] -> Encoding #

omitField :: NominalDiffTimeMicro -> Bool #

ToJSON AccountState 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

toJSON :: AccountState -> Value #

toEncoding :: AccountState -> Encoding #

toJSONList :: [AccountState] -> Value #

toEncodingList :: [AccountState] -> Encoding #

omitField :: AccountState -> Bool #

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 #

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 #

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 #

ToJSON EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toJSON :: EpochSize -> Value #

toEncoding :: EpochSize -> Encoding #

toJSONList :: [EpochSize] -> Value #

toEncodingList :: [EpochSize] -> Encoding #

omitField :: EpochSize -> Bool #

ToJSON SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toJSON :: SlotNo -> Value #

toEncoding :: SlotNo -> Encoding #

toJSONList :: [SlotNo] -> Value #

toEncodingList :: [SlotNo] -> Encoding #

omitField :: SlotNo -> Bool #

ToJSON RelativeTime 
Instance details

Defined in Cardano.Slotting.Time

Methods

toJSON :: RelativeTime -> Value #

toEncoding :: RelativeTime -> Encoding #

toJSONList :: [RelativeTime] -> Value #

toEncodingList :: [RelativeTime] -> Encoding #

omitField :: RelativeTime -> Bool #

ToJSON SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

toJSON :: SystemStart -> Value #

toEncoding :: SystemStart -> Encoding #

toJSONList :: [SystemStart] -> Value #

toEncodingList :: [SystemStart] -> Encoding #

omitField :: SystemStart -> Bool #

ToJSON IntSet 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: IntSet -> Value #

toEncoding :: IntSet -> Encoding #

toJSONList :: [IntSet] -> Value #

toEncodingList :: [IntSet] -> Encoding #

omitField :: IntSet -> Bool #

ToJSON Ordering 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Ordering -> Value #

toEncoding :: Ordering -> Encoding #

toJSONList :: [Ordering] -> Value #

toEncodingList :: [Ordering] -> Encoding #

omitField :: Ordering -> Bool #

ToJSON URI 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: URI -> Value #

toEncoding :: URI -> Encoding #

toJSONList :: [URI] -> Value #

toEncodingList :: [URI] -> Encoding #

omitField :: URI -> Bool #

ToJSON Scientific 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Scientific -> Value #

toEncoding :: Scientific -> Encoding #

toJSONList :: [Scientific] -> Value #

toEncodingList :: [Scientific] -> Encoding #

omitField :: Scientific -> Bool #

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Text -> Value #

toEncoding :: Text -> Encoding #

toJSONList :: [Text] -> Value #

toEncodingList :: [Text] -> Encoding #

omitField :: Text -> Bool #

ToJSON Text 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Text -> Value #

toEncoding :: Text -> Encoding #

toJSONList :: [Text] -> Value #

toEncodingList :: [Text] -> Encoding #

omitField :: Text -> Bool #

ToJSON ShortText 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: ShortText -> Value #

toEncoding :: ShortText -> Encoding #

toJSONList :: [ShortText] -> Value #

toEncodingList :: [ShortText] -> Encoding #

omitField :: ShortText -> Bool #

ToJSON CalendarDiffDays 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON Day 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Day -> Value #

toEncoding :: Day -> Encoding #

toJSONList :: [Day] -> Value #

toEncodingList :: [Day] -> Encoding #

omitField :: Day -> Bool #

ToJSON Month 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Month -> Value #

toEncoding :: Month -> Encoding #

toJSONList :: [Month] -> Value #

toEncodingList :: [Month] -> Encoding #

omitField :: Month -> Bool #

ToJSON Quarter 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Quarter -> Value #

toEncoding :: Quarter -> Encoding #

toJSONList :: [Quarter] -> Value #

toEncodingList :: [Quarter] -> Encoding #

omitField :: Quarter -> Bool #

ToJSON QuarterOfYear 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: QuarterOfYear -> Value #

toEncoding :: QuarterOfYear -> Encoding #

toJSONList :: [QuarterOfYear] -> Value #

toEncodingList :: [QuarterOfYear] -> Encoding #

omitField :: QuarterOfYear -> Bool #

ToJSON DayOfWeek 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DayOfWeek -> Value #

toEncoding :: DayOfWeek -> Encoding #

toJSONList :: [DayOfWeek] -> Value #

toEncodingList :: [DayOfWeek] -> Encoding #

omitField :: DayOfWeek -> Bool #

ToJSON DiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DiffTime -> Value #

toEncoding :: DiffTime -> Encoding #

toJSONList :: [DiffTime] -> Value #

toEncodingList :: [DiffTime] -> Encoding #

omitField :: DiffTime -> Bool #

ToJSON NominalDiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON SystemTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: SystemTime -> Value #

toEncoding :: SystemTime -> Encoding #

toJSONList :: [SystemTime] -> Value #

toEncodingList :: [SystemTime] -> Encoding #

omitField :: SystemTime -> Bool #

ToJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: UTCTime -> Value #

toEncoding :: UTCTime -> Encoding #

toJSONList :: [UTCTime] -> Value #

toEncodingList :: [UTCTime] -> Encoding #

omitField :: UTCTime -> Bool #

ToJSON CalendarDiffTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

ToJSON LocalTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: LocalTime -> Value #

toEncoding :: LocalTime -> Encoding #

toJSONList :: [LocalTime] -> Value #

toEncodingList :: [LocalTime] -> Encoding #

omitField :: LocalTime -> Bool #

ToJSON TimeOfDay 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: TimeOfDay -> Value #

toEncoding :: TimeOfDay -> Encoding #

toJSONList :: [TimeOfDay] -> Value #

toEncodingList :: [TimeOfDay] -> Encoding #

omitField :: TimeOfDay -> Bool #

ToJSON ZonedTime 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: ZonedTime -> Value #

toEncoding :: ZonedTime -> Encoding #

toJSONList :: [ZonedTime] -> Value #

toEncodingList :: [ZonedTime] -> Encoding #

omitField :: ZonedTime -> Bool #

ToJSON UUID 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: UUID -> Value #

toEncoding :: UUID -> Encoding #

toJSONList :: [UUID] -> Value #

toEncodingList :: [UUID] -> Encoding #

omitField :: UUID -> Bool #

ToJSON Integer 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Integer -> Value #

toEncoding :: Integer -> Encoding #

toJSONList :: [Integer] -> Value #

toEncodingList :: [Integer] -> Encoding #

omitField :: Integer -> Bool #

ToJSON Natural 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Natural -> Value #

toEncoding :: Natural -> Encoding #

toJSONList :: [Natural] -> Value #

toEncodingList :: [Natural] -> Encoding #

omitField :: Natural -> Bool #

ToJSON () 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: () -> Value #

toEncoding :: () -> Encoding #

toJSONList :: [()] -> Value #

toEncodingList :: [()] -> Encoding #

omitField :: () -> Bool #

ToJSON Bool 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Bool -> Value #

toEncoding :: Bool -> Encoding #

toJSONList :: [Bool] -> Value #

toEncodingList :: [Bool] -> Encoding #

omitField :: Bool -> Bool #

ToJSON Char 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Char -> Value #

toEncoding :: Char -> Encoding #

toJSONList :: [Char] -> Value #

toEncodingList :: [Char] -> Encoding #

omitField :: Char -> Bool #

ToJSON Double 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Double -> Value #

toEncoding :: Double -> Encoding #

toJSONList :: [Double] -> Value #

toEncodingList :: [Double] -> Encoding #

omitField :: Double -> Bool #

ToJSON Float 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Float -> Value #

toEncoding :: Float -> Encoding #

toJSONList :: [Float] -> Value #

toEncodingList :: [Float] -> Encoding #

omitField :: Float -> Bool #

ToJSON Int 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Int -> Value #

toEncoding :: Int -> Encoding #

toJSONList :: [Int] -> Value #

toEncodingList :: [Int] -> Encoding #

omitField :: Int -> Bool #

ToJSON Word 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Word -> Value #

toEncoding :: Word -> Encoding #

toJSONList :: [Word] -> Value #

toEncodingList :: [Word] -> Encoding #

omitField :: Word -> Bool #

ToJSON v => ToJSON (KeyMap v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: KeyMap v -> Value #

toEncoding :: KeyMap v -> Encoding #

toJSONList :: [KeyMap v] -> Value #

toEncodingList :: [KeyMap v] -> Encoding #

omitField :: KeyMap v -> Bool #

ToJSON a => ToJSON (Identity a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Identity a -> Value #

toEncoding :: Identity a -> Encoding #

toJSONList :: [Identity a] -> Value #

toEncodingList :: [Identity a] -> Encoding #

omitField :: Identity a -> Bool #

ToJSON a => ToJSON (First a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: First a -> Value #

toEncoding :: First a -> Encoding #

toJSONList :: [First a] -> Value #

toEncodingList :: [First a] -> Encoding #

omitField :: First a -> Bool #

ToJSON a => ToJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Last a -> Value #

toEncoding :: Last a -> Encoding #

toJSONList :: [Last a] -> Value #

toEncodingList :: [Last a] -> Encoding #

omitField :: Last a -> Bool #

ToJSON a => ToJSON (Down a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Down a -> Value #

toEncoding :: Down a -> Encoding #

toJSONList :: [Down a] -> Value #

toEncodingList :: [Down a] -> Encoding #

omitField :: Down a -> Bool #

ToJSON a => ToJSON (First a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: First a -> Value #

toEncoding :: First a -> Encoding #

toJSONList :: [First a] -> Value #

toEncodingList :: [First a] -> Encoding #

omitField :: First a -> Bool #

ToJSON a => ToJSON (Last a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Last a -> Value #

toEncoding :: Last a -> Encoding #

toJSONList :: [Last a] -> Value #

toEncodingList :: [Last a] -> Encoding #

omitField :: Last a -> Bool #

ToJSON a => ToJSON (Max a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Max a -> Value #

toEncoding :: Max a -> Encoding #

toJSONList :: [Max a] -> Value #

toEncodingList :: [Max a] -> Encoding #

omitField :: Max a -> Bool #

ToJSON a => ToJSON (Min a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Min a -> Value #

toEncoding :: Min a -> Encoding #

toJSONList :: [Min a] -> Value #

toEncodingList :: [Min a] -> Encoding #

omitField :: Min a -> Bool #

ToJSON a => ToJSON (WrappedMonoid a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: WrappedMonoid a -> Value #

toEncoding :: WrappedMonoid a -> Encoding #

toJSONList :: [WrappedMonoid a] -> Value #

toEncodingList :: [WrappedMonoid a] -> Encoding #

omitField :: WrappedMonoid a -> Bool #

ToJSON a => ToJSON (Dual a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Dual a -> Value #

toEncoding :: Dual a -> Encoding #

toJSONList :: [Dual a] -> Value #

toEncodingList :: [Dual a] -> Encoding #

omitField :: Dual a -> Bool #

ToJSON a => ToJSON (NonEmpty a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: NonEmpty a -> Value #

toEncoding :: NonEmpty a -> Encoding #

toJSONList :: [NonEmpty a] -> Value #

toEncodingList :: [NonEmpty a] -> Encoding #

omitField :: NonEmpty a -> Bool #

(Generic a, GToJSON' Value Zero (Rep a), GToJSON' Encoding Zero (Rep a)) => ToJSON (Generically a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Generically a -> Value #

toEncoding :: Generically a -> Encoding #

toJSONList :: [Generically a] -> Value #

toEncodingList :: [Generically a] -> Encoding #

omitField :: Generically a -> Bool #

(ToJSON a, Integral a) => ToJSON (Ratio a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Ratio a -> Value #

toEncoding :: Ratio a -> Encoding #

toJSONList :: [Ratio a] -> Value #

toEncodingList :: [Ratio a] -> Encoding #

omitField :: Ratio a -> Bool #

ToJSON (Address ByronAddr) 
Instance details

Defined in Cardano.Api.Address

ToJSON (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

IsCardanoEra era => ToJSON (AddressInEra era) 
Instance details

Defined in Cardano.Api.Address

Methods

toJSON :: AddressInEra era -> Value #

toEncoding :: AddressInEra era -> Encoding #

toJSONList :: [AddressInEra era] -> Value #

toEncodingList :: [AddressInEra era] -> Encoding #

omitField :: AddressInEra era -> Bool #

ToJSON (ShelleyBasedEra era) 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Methods

toJSON :: ShelleyBasedEra era -> Value #

toEncoding :: ShelleyBasedEra era -> Encoding #

toJSONList :: [ShelleyBasedEra era] -> Value #

toEncodingList :: [ShelleyBasedEra era] -> Encoding #

omitField :: ShelleyBasedEra era -> Bool #

ToJSON (CardanoEra era) 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

toJSON :: CardanoEra era -> Value #

toEncoding :: CardanoEra era -> Encoding #

toJSONList :: [CardanoEra era] -> Value #

toEncodingList :: [CardanoEra era] -> Encoding #

omitField :: CardanoEra era -> Bool #

ToJSON (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

ToJSON (Hash DRepKey) 
Instance details

Defined in Cardano.Api.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) 
Instance details

Defined in Cardano.Api.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) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toJSON :: Hash PaymentKey -> Value #

toEncoding :: Hash PaymentKey -> Encoding #

toJSONList :: [Hash PaymentKey] -> Value #

toEncodingList :: [Hash PaymentKey] -> Encoding #

omitField :: Hash PaymentKey -> Bool #

ToJSON (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToJSON (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

Methods

toJSON :: Hash ScriptData -> Value #

toEncoding :: Hash ScriptData -> Encoding #

toJSONList :: [Hash ScriptData] -> Value #

toEncodingList :: [Hash ScriptData] -> Encoding #

omitField :: Hash ScriptData -> Bool #

ToJSON (TxValidationError era) 
Instance details

Defined in Cardano.Api.InMode

Methods

toJSON :: TxValidationError era -> Value #

toEncoding :: TxValidationError era -> Encoding #

toJSONList :: [TxValidationError era] -> Value #

toEncodingList :: [TxValidationError era] -> Encoding #

omitField :: TxValidationError era -> Bool #

ToJSON (VerificationKey PaymentKey) Source # 
Instance details

Defined in Hydra.Cardano.Api.VerificationKey

IsCardanoEra era => ToJSON (UTxO era) 
Instance details

Defined in Cardano.Api.Query

Methods

toJSON :: UTxO era -> Value #

toEncoding :: UTxO era -> Encoding #

toJSONList :: [UTxO era] -> Value #

toEncodingList :: [UTxO era] -> Encoding #

omitField :: UTxO era -> Bool #

IsShelleyBasedEra era => ToJSON (DebugLedgerState era) 
Instance details

Defined in Cardano.Api.Query.Types

Methods

toJSON :: DebugLedgerState era -> Value #

toEncoding :: DebugLedgerState era -> Encoding #

toJSONList :: [DebugLedgerState era] -> Value #

toEncodingList :: [DebugLedgerState era] -> Encoding #

omitField :: DebugLedgerState era -> Bool #

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

Defined in Hydra.Cardano.Api.PlutusScript

Methods

toJSON :: PlutusScript lang -> Value #

toEncoding :: PlutusScript lang -> Encoding #

toJSONList :: [PlutusScript lang] -> Value #

toEncodingList :: [PlutusScript lang] -> Encoding #

omitField :: PlutusScript lang -> Bool #

IsCardanoEra era => ToJSON (ReferenceScript era) 
Instance details

Defined in Cardano.Api.Script

Methods

toJSON :: ReferenceScript era -> Value #

toEncoding :: ReferenceScript era -> Encoding #

toJSONList :: [ReferenceScript era] -> Value #

toEncodingList :: [ReferenceScript era] -> Encoding #

omitField :: ReferenceScript era -> Bool #

SerialiseAsBech32 a => ToJSON (UsingBech32 a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

toJSON :: UsingBech32 a -> Value #

toEncoding :: UsingBech32 a -> Encoding #

toJSONList :: [UsingBech32 a] -> Value #

toEncodingList :: [UsingBech32 a] -> Encoding #

omitField :: UsingBech32 a -> Bool #

SerialiseAsRawBytes a => ToJSON (UsingRawBytesHex a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

toJSON :: UsingRawBytesHex a -> Value #

toEncoding :: UsingRawBytesHex a -> Encoding #

toJSONList :: [UsingRawBytesHex a] -> Value #

toEncodingList :: [UsingRawBytesHex a] -> Encoding #

omitField :: UsingRawBytesHex a -> Bool #

IsCardanoEra era => ToJSON (TxOutValue era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

toJSON :: TxOutValue era -> Value #

toEncoding :: TxOutValue era -> Encoding #

toJSONList :: [TxOutValue era] -> Value #

toEncodingList :: [TxOutValue era] -> Encoding #

omitField :: TxOutValue era -> Bool #

Show a => ToJSON (ShowOf a) 
Instance details

Defined in Cardano.Api.Via.ShowOf

Methods

toJSON :: ShowOf a -> Value #

toEncoding :: ShowOf a -> Encoding #

toJSONList :: [ShowOf a] -> Value #

toEncodingList :: [ShowOf a] -> Encoding #

omitField :: ShowOf a -> Bool #

ToJSON (AlonzoContextError era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Plutus.TxInfo

Methods

toJSON :: AlonzoContextError era -> Value #

toEncoding :: AlonzoContextError era -> Encoding #

toJSONList :: [AlonzoContextError era] -> Value #

toEncodingList :: [AlonzoContextError era] -> Encoding #

omitField :: AlonzoContextError era -> Bool #

AlonzoEraScript era => ToJSON (AlonzoScript era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Methods

toJSON :: AlonzoScript era -> Value #

toEncoding :: AlonzoScript era -> Encoding #

toJSONList :: [AlonzoScript era] -> Value #

toEncodingList :: [AlonzoScript era] -> Encoding #

omitField :: AlonzoScript era -> Bool #

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

Defined in Cardano.Ledger.Alonzo.TxOut

Methods

toJSON :: AlonzoTxOut era -> Value #

toEncoding :: AlonzoTxOut era -> Encoding #

toJSONList :: [AlonzoTxOut era] -> Value #

toEncodingList :: [AlonzoTxOut era] -> Encoding #

omitField :: AlonzoTxOut era -> Bool #

Crypto c => ToJSON (CommitteeMemberState c) 
Instance details

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

Methods

toJSON :: CommitteeMemberState c -> Value #

toEncoding :: CommitteeMemberState c -> Encoding #

toJSONList :: [CommitteeMemberState c] -> Value #

toEncodingList :: [CommitteeMemberState c] -> Encoding #

omitField :: CommitteeMemberState c -> Bool #

Crypto c => ToJSON (CommitteeMembersState c) 
Instance details

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

Crypto c => ToJSON (HotCredAuthStatus c) 
Instance details

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

Methods

toJSON :: HotCredAuthStatus c -> Value #

toEncoding :: HotCredAuthStatus c -> Encoding #

toJSONList :: [HotCredAuthStatus c] -> Value #

toEncodingList :: [HotCredAuthStatus c] -> Encoding #

omitField :: HotCredAuthStatus c -> Bool #

ToJSON (PlutusPurpose AsIndex era) => ToJSON (BabbageContextError era) 
Instance details

Defined in Cardano.Ledger.Babbage.TxInfo

Methods

toJSON :: BabbageContextError era -> Value #

toEncoding :: BabbageContextError era -> Encoding #

toJSONList :: [BabbageContextError era] -> Value #

toEncodingList :: [BabbageContextError era] -> Encoding #

omitField :: BabbageContextError era -> Bool #

(Era era, ToJSON (Datum era), ToJSON (Script era), Val (Value era)) => ToJSON (BabbageTxOut era) 
Instance details

Defined in Cardano.Ledger.Babbage.TxOut

Methods

toJSON :: BabbageTxOut era -> Value #

toEncoding :: BabbageTxOut era -> Encoding #

toJSONList :: [BabbageTxOut era] -> Value #

toEncodingList :: [BabbageTxOut era] -> Encoding #

omitField :: BabbageTxOut era -> Bool #

ToJSON a => ToJSON (ATxAux a) 
Instance details

Defined in Cardano.Chain.UTxO.TxAux

Methods

toJSON :: ATxAux a -> Value #

toEncoding :: ATxAux a -> Encoding #

toJSONList :: [ATxAux a] -> Value #

toEncodingList :: [ATxAux a] -> Encoding #

omitField :: ATxAux a -> Bool #

Crypto c => ToJSON (ConwayGenesis c) 
Instance details

Defined in Cardano.Ledger.Conway.Genesis

Methods

toJSON :: ConwayGenesis c -> Value #

toEncoding :: ConwayGenesis c -> Encoding #

toJSONList :: [ConwayGenesis c] -> Value #

toEncodingList :: [ConwayGenesis c] -> Encoding #

omitField :: ConwayGenesis c -> Bool #

EraPParams era => ToJSON (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toJSON :: ConwayGovState era -> Value #

toEncoding :: ConwayGovState era -> Encoding #

toJSONList :: [ConwayGovState era] -> Value #

toEncodingList :: [ConwayGovState era] -> Encoding #

omitField :: ConwayGovState era -> Bool #

EraPParams era => ToJSON (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toJSON :: EnactState era -> Value #

toEncoding :: EnactState era -> Encoding #

toJSONList :: [EnactState era] -> Value #

toEncodingList :: [EnactState era] -> Encoding #

omitField :: EnactState era -> Bool #

EraPParams era => ToJSON (PulsingSnapshot era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toJSON :: PulsingSnapshot era -> Value #

toEncoding :: PulsingSnapshot era -> Encoding #

toJSONList :: [PulsingSnapshot era] -> Value #

toEncodingList :: [PulsingSnapshot era] -> Encoding #

omitField :: PulsingSnapshot era -> Bool #

EraPParams era => ToJSON (RatifyState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toJSON :: RatifyState era -> Value #

toEncoding :: RatifyState era -> Encoding #

toJSONList :: [RatifyState era] -> Value #

toEncodingList :: [RatifyState era] -> Encoding #

omitField :: RatifyState era -> Bool #

EraPParams era => ToJSON (Committee era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: Committee era -> Value #

toEncoding :: Committee era -> Encoding #

toJSONList :: [Committee era] -> Value #

toEncodingList :: [Committee era] -> Encoding #

omitField :: Committee era -> Bool #

EraPParams era => ToJSON (GovAction era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: GovAction era -> Value #

toEncoding :: GovAction era -> Encoding #

toJSONList :: [GovAction era] -> Value #

toEncodingList :: [GovAction era] -> Encoding #

omitField :: GovAction era -> Bool #

Crypto c => ToJSON (GovActionId c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: GovActionId c -> Value #

toEncoding :: GovActionId c -> Encoding #

toJSONList :: [GovActionId c] -> Value #

toEncodingList :: [GovActionId c] -> Encoding #

omitField :: GovActionId c -> Bool #

EraPParams era => ToJSON (GovActionState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: GovActionState era -> Value #

toEncoding :: GovActionState era -> Encoding #

toJSONList :: [GovActionState era] -> Value #

toEncodingList :: [GovActionState era] -> Encoding #

omitField :: GovActionState era -> Bool #

EraPParams era => ToJSON (ProposalProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: ProposalProcedure era -> Value #

toEncoding :: ProposalProcedure era -> Encoding #

toJSONList :: [ProposalProcedure era] -> Value #

toEncodingList :: [ProposalProcedure era] -> Encoding #

omitField :: ProposalProcedure era -> Bool #

Crypto c => ToJSON (Voter c) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: Voter c -> Value #

toEncoding :: Voter c -> Encoding #

toJSONList :: [Voter c] -> Value #

toEncodingList :: [Voter c] -> Encoding #

omitField :: Voter c -> Bool #

EraPParams era => ToJSON (VotingProcedure era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: VotingProcedure era -> Value #

toEncoding :: VotingProcedure era -> Encoding #

toJSONList :: [VotingProcedure era] -> Value #

toEncodingList :: [VotingProcedure era] -> Encoding #

omitField :: VotingProcedure era -> Bool #

EraPParams era => ToJSON (VotingProcedures era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: VotingProcedures era -> Value #

toEncoding :: VotingProcedures era -> Encoding #

toJSONList :: [VotingProcedures era] -> Value #

toEncodingList :: [VotingProcedures era] -> Encoding #

omitField :: VotingProcedures era -> Bool #

ToJSON (UpgradeConwayPParams Identity) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

toJSON :: UpgradeConwayPParams Identity -> Value #

toEncoding :: UpgradeConwayPParams Identity -> Encoding #

toJSONList :: [UpgradeConwayPParams Identity] -> Value #

toEncodingList :: [UpgradeConwayPParams Identity] -> Encoding #

omitField :: UpgradeConwayPParams Identity -> Bool #

Crypto c => ToJSON (ConwayDelegCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

toJSON :: ConwayDelegCert c -> Value #

toEncoding :: ConwayDelegCert c -> Encoding #

toJSONList :: [ConwayDelegCert c] -> Value #

toEncodingList :: [ConwayDelegCert c] -> Encoding #

omitField :: ConwayDelegCert c -> Bool #

Crypto c => ToJSON (ConwayGovCert c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

toJSON :: ConwayGovCert c -> Value #

toEncoding :: ConwayGovCert c -> Encoding #

toJSONList :: [ConwayGovCert c] -> Value #

toEncodingList :: [ConwayGovCert c] -> Encoding #

omitField :: ConwayGovCert c -> Bool #

Era era => ToJSON (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

toJSON :: ConwayTxCert era -> Value #

toEncoding :: ConwayTxCert era -> Encoding #

toJSONList :: [ConwayTxCert era] -> Value #

toEncodingList :: [ConwayTxCert era] -> Encoding #

omitField :: ConwayTxCert era -> Bool #

Crypto c => ToJSON (Delegatee c) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

toJSON :: Delegatee c -> Value #

toEncoding :: Delegatee c -> Encoding #

toJSONList :: [Delegatee c] -> Value #

toEncodingList :: [Delegatee c] -> Encoding #

omitField :: Delegatee c -> Bool #

(ToJSON (TxCert era), ToJSON (PlutusPurpose AsIndex era), ToJSON (PlutusPurpose AsItem era)) => ToJSON (ConwayContextError era) 
Instance details

Defined in Cardano.Ledger.Conway.TxInfo

Methods

toJSON :: ConwayContextError era -> Value #

toEncoding :: ConwayContextError era -> Encoding #

toJSONList :: [ConwayContextError era] -> Value #

toEncodingList :: [ConwayContextError era] -> Encoding #

omitField :: ConwayContextError era -> Bool #

ToJSON (Addr c) 
Instance details

Defined in Cardano.Ledger.Address

Methods

toJSON :: Addr c -> Value #

toEncoding :: Addr c -> Encoding #

toJSONList :: [Addr c] -> Value #

toEncodingList :: [Addr c] -> Encoding #

omitField :: Addr c -> Bool #

Crypto c => ToJSON (RewardAcnt c) 
Instance details

Defined in Cardano.Ledger.Address

Methods

toJSON :: RewardAcnt c -> Value #

toEncoding :: RewardAcnt c -> Encoding #

toJSONList :: [RewardAcnt c] -> Value #

toEncodingList :: [RewardAcnt c] -> Encoding #

omitField :: RewardAcnt c -> Bool #

Crypto c => ToJSON (AuxiliaryDataHash c) 
Instance details

Defined in Cardano.Ledger.AuxiliaryData

Methods

toJSON :: AuxiliaryDataHash c -> Value #

toEncoding :: AuxiliaryDataHash c -> Encoding #

toJSONList :: [AuxiliaryDataHash c] -> Value #

toEncodingList :: [AuxiliaryDataHash c] -> Encoding #

omitField :: AuxiliaryDataHash c -> Bool #

Crypto c => ToJSON (Anchor c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: Anchor c -> Value #

toEncoding :: Anchor c -> Encoding #

toJSONList :: [Anchor c] -> Value #

toEncodingList :: [Anchor c] -> Encoding #

omitField :: Anchor c -> Bool #

Crypto c => ToJSON (BlocksMade c) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: BlocksMade c -> Value #

toEncoding :: BlocksMade c -> Encoding #

toJSONList :: [BlocksMade c] -> Value #

toEncodingList :: [BlocksMade c] -> Encoding #

omitField :: BlocksMade c -> Bool #

Era era => ToJSON (CertState era) 
Instance details

Defined in Cardano.Ledger.CertState

Methods

toJSON :: CertState era -> Value #

toEncoding :: CertState era -> Encoding #

toJSONList :: [CertState era] -> Value #

toEncodingList :: [CertState era] -> Encoding #

omitField :: CertState era -> Bool #

Era era => ToJSON (CommitteeState era) 
Instance details

Defined in Cardano.Ledger.CertState

Methods

toJSON :: CommitteeState era -> Value #

toEncoding :: CommitteeState era -> Encoding #

toJSONList :: [CommitteeState era] -> Value #

toEncodingList :: [CommitteeState era] -> Encoding #

omitField :: CommitteeState era -> Bool #

Era era => ToJSON (DState era) 
Instance details

Defined in Cardano.Ledger.CertState

Methods

toJSON :: DState era -> Value #

toEncoding :: DState era -> Encoding #

toJSONList :: [DState era] -> Value #

toEncodingList :: [DState era] -> Encoding #

omitField :: DState era -> Bool #

Crypto c => ToJSON (FutureGenDeleg c) 
Instance details

Defined in Cardano.Ledger.CertState

Methods

toJSON :: FutureGenDeleg c -> Value #

toEncoding :: FutureGenDeleg c -> Encoding #

toJSONList :: [FutureGenDeleg c] -> Value #

toEncodingList :: [FutureGenDeleg c] -> Encoding #

omitField :: FutureGenDeleg c -> Bool #

Crypto c => ToJSON (InstantaneousRewards c) 
Instance details

Defined in Cardano.Ledger.CertState

Methods

toJSON :: InstantaneousRewards c -> Value #

toEncoding :: InstantaneousRewards c -> Encoding #

toJSONList :: [InstantaneousRewards c] -> Value #

toEncodingList :: [InstantaneousRewards c] -> Encoding #

omitField :: InstantaneousRewards c -> Bool #

Era era => ToJSON (PState era) 
Instance details

Defined in Cardano.Ledger.CertState

Methods

toJSON :: PState era -> Value #

toEncoding :: PState era -> Encoding #

toJSONList :: [PState era] -> Value #

toEncodingList :: [PState era] -> Encoding #

omitField :: PState era -> Bool #

ToJSON (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toJSON :: CompactForm Coin -> Value #

toEncoding :: CompactForm Coin -> Encoding #

toJSONList :: [CompactForm Coin] -> Value #

toEncodingList :: [CompactForm Coin] -> Encoding #

omitField :: CompactForm Coin -> Bool #

ToJSON (CompactForm DeltaCoin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toJSON :: CompactForm DeltaCoin -> Value #

toEncoding :: CompactForm DeltaCoin -> Encoding #

toJSONList :: [CompactForm DeltaCoin] -> Value #

toEncodingList :: [CompactForm DeltaCoin] -> Encoding #

omitField :: CompactForm DeltaCoin -> Bool #

ToJSON (PParamsHKD Identity era) => ToJSON (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toJSON :: PParams era -> Value #

toEncoding :: PParams era -> Encoding #

toJSONList :: [PParams era] -> Value #

toEncodingList :: [PParams era] -> Encoding #

omitField :: PParams era -> Bool #

ToJSON (PParamsHKD StrictMaybe era) => ToJSON (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toJSON :: PParamsUpdate era -> Value #

toEncoding :: PParamsUpdate era -> Encoding #

toJSONList :: [PParamsUpdate era] -> Value #

toEncodingList :: [PParamsUpdate era] -> Encoding #

omitField :: PParamsUpdate era -> Bool #

Crypto c => ToJSON (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

toJSON :: PoolCert c -> Value #

toEncoding :: PoolCert c -> Encoding #

toJSONList :: [PoolCert c] -> Value #

toEncodingList :: [PoolCert c] -> Encoding #

omitField :: PoolCert c -> Bool #

Crypto c => ToJSON (StakeReference c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

toJSON :: StakeReference c -> Value #

toEncoding :: StakeReference c -> Encoding #

toJSONList :: [StakeReference c] -> Value #

toEncodingList :: [StakeReference c] -> Encoding #

omitField :: StakeReference c -> Bool #

Crypto c => ToJSON (DRep c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

toJSON :: DRep c -> Value #

toEncoding :: DRep c -> Encoding #

toJSONList :: [DRep c] -> Value #

toEncodingList :: [DRep c] -> Encoding #

omitField :: DRep c -> Bool #

Crypto c => ToJSON (DRepState c) 
Instance details

Defined in Cardano.Ledger.DRep

Methods

toJSON :: DRepState c -> Value #

toEncoding :: DRepState c -> Encoding #

toJSONList :: [DRepState c] -> Value #

toEncodingList :: [DRepState c] -> Encoding #

omitField :: DRepState c -> Bool #

Crypto c => ToJSON (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

toJSON :: ScriptHash c -> Value #

toEncoding :: ScriptHash c -> Encoding #

toJSONList :: [ScriptHash c] -> Value #

toEncodingList :: [ScriptHash c] -> Encoding #

omitField :: ScriptHash c -> Bool #

Crypto c => ToJSON (GenDelegPair c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

toJSON :: GenDelegPair c -> Value #

toEncoding :: GenDelegPair c -> Encoding #

toJSONList :: [GenDelegPair c] -> Value #

toEncodingList :: [GenDelegPair c] -> Encoding #

omitField :: GenDelegPair c -> Bool #

Crypto c => ToJSON (GenDelegs c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

toJSON :: GenDelegs c -> Value #

toEncoding :: GenDelegs c -> Encoding #

toJSONList :: [GenDelegs c] -> Value #

toEncodingList :: [GenDelegs c] -> Encoding #

omitField :: GenDelegs c -> Bool #

Era era => ToJSON (Datum era) 
Instance details

Defined in Cardano.Ledger.Plutus.Data

Methods

toJSON :: Datum era -> Value #

toEncoding :: Datum era -> Encoding #

toJSONList :: [Datum era] -> Value #

toEncodingList :: [Datum era] -> Encoding #

omitField :: Datum era -> Bool #

ToJSON a => ToJSON (ExUnits' a) 
Instance details

Defined in Cardano.Ledger.Plutus.ExUnits

Methods

toJSON :: ExUnits' a -> Value #

toEncoding :: ExUnits' a -> Encoding #

toJSONList :: [ExUnits' a] -> Value #

toEncodingList :: [ExUnits' a] -> Encoding #

omitField :: ExUnits' a -> Bool #

ToJSON (TxOutSource c) 
Instance details

Defined in Cardano.Ledger.Plutus.TxInfo

Methods

toJSON :: TxOutSource c -> Value #

toEncoding :: TxOutSource c -> Encoding #

toJSONList :: [TxOutSource c] -> Value #

toEncodingList :: [TxOutSource c] -> Encoding #

omitField :: TxOutSource c -> Bool #

Crypto c => ToJSON (IndividualPoolStake c) 
Instance details

Defined in Cardano.Ledger.PoolDistr

Methods

toJSON :: IndividualPoolStake c -> Value #

toEncoding :: IndividualPoolStake c -> Encoding #

toJSONList :: [IndividualPoolStake c] -> Value #

toEncodingList :: [IndividualPoolStake c] -> Encoding #

omitField :: IndividualPoolStake c -> Bool #

Crypto c => ToJSON (PoolDistr c) 
Instance details

Defined in Cardano.Ledger.PoolDistr

Methods

toJSON :: PoolDistr c -> Value #

toEncoding :: PoolDistr c -> Encoding #

toJSONList :: [PoolDistr c] -> Value #

toEncodingList :: [PoolDistr c] -> Encoding #

omitField :: PoolDistr c -> Bool #

Crypto c => ToJSON (PoolParams c) 
Instance details

Defined in Cardano.Ledger.PoolParams

Methods

toJSON :: PoolParams c -> Value #

toEncoding :: PoolParams c -> Encoding #

toJSONList :: [PoolParams c] -> Value #

toEncodingList :: [PoolParams c] -> Encoding #

omitField :: PoolParams c -> Bool #

Crypto c => ToJSON (TxId c) 
Instance details

Defined in Cardano.Ledger.TxIn

Methods

toJSON :: TxId c -> Value #

toEncoding :: TxId c -> Encoding #

toJSONList :: [TxId c] -> Value #

toEncodingList :: [TxId c] -> Encoding #

omitField :: TxId c -> Bool #

Crypto c => ToJSON (TxIn c) 
Instance details

Defined in Cardano.Ledger.TxIn

Methods

toJSON :: TxIn c -> Value #

toEncoding :: TxIn c -> Encoding #

toJSONList :: [TxIn c] -> Value #

toEncodingList :: [TxIn c] -> Encoding #

omitField :: TxIn c -> Bool #

(Era era, ToJSON (TxOut era)) => ToJSON (UTxO era) 
Instance details

Defined in Cardano.Ledger.UTxO

Methods

toJSON :: UTxO era -> Value #

toEncoding :: UTxO era -> Encoding #

toJSONList :: [UTxO era] -> Value #

toEncodingList :: [UTxO era] -> Encoding #

omitField :: UTxO era -> Bool #

Crypto c => ToJSON (MaryValue c) 
Instance details

Defined in Cardano.Ledger.Mary.Value

Methods

toJSON :: MaryValue c -> Value #

toEncoding :: MaryValue c -> Encoding #

toJSONList :: [MaryValue c] -> Value #

toEncodingList :: [MaryValue c] -> Encoding #

omitField :: MaryValue c -> Bool #

Crypto c => ToJSON (MultiAsset c) 
Instance details

Defined in Cardano.Ledger.Mary.Value

Methods

toJSON :: MultiAsset c -> Value #

toEncoding :: MultiAsset c -> Encoding #

toJSONList :: [MultiAsset c] -> Value #

toEncodingList :: [MultiAsset c] -> Encoding #

omitField :: MultiAsset c -> Bool #

Crypto c => ToJSON (PolicyID c) 
Instance details

Defined in Cardano.Ledger.Mary.Value

Methods

toJSON :: PolicyID c -> Value #

toEncoding :: PolicyID c -> Encoding #

toJSONList :: [PolicyID c] -> Value #

toEncodingList :: [PolicyID c] -> Encoding #

omitField :: PolicyID c -> Bool #

Crypto c => ToJSON (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toJSON :: ShelleyGenesis c -> Value #

toEncoding :: ShelleyGenesis c -> Encoding #

toJSONList :: [ShelleyGenesis c] -> Value #

toEncodingList :: [ShelleyGenesis c] -> Encoding #

omitField :: ShelleyGenesis c -> Bool #

Crypto c => ToJSON (ShelleyGenesisStaking c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toJSON :: ShelleyGenesisStaking c -> Value #

toEncoding :: ShelleyGenesisStaking c -> Encoding #

toJSONList :: [ShelleyGenesisStaking c] -> Value #

toEncodingList :: [ShelleyGenesisStaking c] -> Encoding #

omitField :: ShelleyGenesisStaking c -> Bool #

Era era => ToJSON (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

toJSON :: Constitution era -> Value #

toEncoding :: Constitution era -> Encoding #

toJSONList :: [Constitution era] -> Value #

toEncodingList :: [Constitution era] -> Encoding #

omitField :: Constitution era -> Bool #

EraPParams era => ToJSON (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

toJSON :: ShelleyGovState era -> Value #

toEncoding :: ShelleyGovState era -> Encoding #

toJSONList :: [ShelleyGovState era] -> Value #

toEncodingList :: [ShelleyGovState era] -> Encoding #

omitField :: ShelleyGovState era -> Bool #

(EraTxOut era, EraGov era) => ToJSON (EpochState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

toJSON :: EpochState era -> Value #

toEncoding :: EpochState era -> Encoding #

toJSONList :: [EpochState era] -> Value #

toEncodingList :: [EpochState era] -> Encoding #

omitField :: EpochState era -> Bool #

Crypto c => ToJSON (IncrementalStake c) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

toJSON :: IncrementalStake c -> Value #

toEncoding :: IncrementalStake c -> Encoding #

toJSONList :: [IncrementalStake c] -> Value #

toEncodingList :: [IncrementalStake c] -> Encoding #

omitField :: IncrementalStake c -> Bool #

(EraTxOut era, EraGov era) => ToJSON (LedgerState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

toJSON :: LedgerState era -> Value #

toEncoding :: LedgerState era -> Encoding #

toJSONList :: [LedgerState era] -> Value #

toEncodingList :: [LedgerState era] -> Encoding #

omitField :: LedgerState era -> Bool #

(EraTxOut era, EraGov era) => ToJSON (UTxOState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

toJSON :: UTxOState era -> Value #

toEncoding :: UTxOState era -> Encoding #

toJSONList :: [UTxOState era] -> Value #

toEncodingList :: [UTxOState era] -> Encoding #

omitField :: UTxOState era -> Bool #

EraPParams era => ToJSON (ProposedPPUpdates era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

toJSON :: ProposedPPUpdates era -> Value #

toEncoding :: ProposedPPUpdates era -> Encoding #

toJSONList :: [ProposedPPUpdates era] -> Value #

toEncodingList :: [ProposedPPUpdates era] -> Encoding #

omitField :: ProposedPPUpdates era -> Bool #

Crypto c => ToJSON (TransitionConfig (ShelleyEra c)) 
Instance details

Defined in Cardano.Ledger.Shelley.Transition

Methods

toJSON :: TransitionConfig (ShelleyEra c) -> Value #

toEncoding :: TransitionConfig (ShelleyEra c) -> Encoding #

toJSONList :: [TransitionConfig (ShelleyEra c)] -> Value #

toEncodingList :: [TransitionConfig (ShelleyEra c)] -> Encoding #

omitField :: TransitionConfig (ShelleyEra c) -> Bool #

Crypto c => ToJSON (GenesisDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toJSON :: GenesisDelegCert c -> Value #

toEncoding :: GenesisDelegCert c -> Encoding #

toJSONList :: [GenesisDelegCert c] -> Value #

toEncodingList :: [GenesisDelegCert c] -> Encoding #

omitField :: GenesisDelegCert c -> Bool #

Crypto c => ToJSON (MIRCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toJSON :: MIRCert c -> Value #

toEncoding :: MIRCert c -> Encoding #

toJSONList :: [MIRCert c] -> Value #

toEncodingList :: [MIRCert c] -> Encoding #

omitField :: MIRCert c -> Bool #

Crypto c => ToJSON (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toJSON :: MIRTarget c -> Value #

toEncoding :: MIRTarget c -> Encoding #

toJSONList :: [MIRTarget c] -> Value #

toEncodingList :: [MIRTarget c] -> Encoding #

omitField :: MIRTarget c -> Bool #

Crypto c => ToJSON (ShelleyDelegCert c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toJSON :: ShelleyDelegCert c -> Value #

toEncoding :: ShelleyDelegCert c -> Encoding #

toJSONList :: [ShelleyDelegCert c] -> Value #

toEncodingList :: [ShelleyDelegCert c] -> Encoding #

omitField :: ShelleyDelegCert c -> Bool #

Era era => ToJSON (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toJSON :: ShelleyTxCert era -> Value #

toEncoding :: ShelleyTxCert era -> Encoding #

toJSONList :: [ShelleyTxCert era] -> Value #

toEncodingList :: [ShelleyTxCert era] -> Encoding #

omitField :: ShelleyTxCert era -> Bool #

(Era era, Val (Value era)) => ToJSON (ShelleyTxOut era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxOut

Methods

toJSON :: ShelleyTxOut era -> Value #

toEncoding :: ShelleyTxOut era -> Encoding #

toJSONList :: [ShelleyTxOut era] -> Value #

toEncodingList :: [ShelleyTxOut era] -> Encoding #

omitField :: ShelleyTxOut era -> Bool #

ToJSON a => ToJSON (WithOrigin a) 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toJSON :: WithOrigin a -> Value #

toEncoding :: WithOrigin a -> Encoding #

toJSONList :: [WithOrigin a] -> Value #

toEncodingList :: [WithOrigin a] -> Encoding #

omitField :: WithOrigin a -> Bool #

ToJSON a => ToJSON (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Methods

toJSON :: StrictMaybe a -> Value #

toEncoding :: StrictMaybe a -> Encoding #

toJSONList :: [StrictMaybe a] -> Value #

toEncodingList :: [StrictMaybe a] -> Encoding #

omitField :: StrictMaybe a -> Bool #

ToJSON a => ToJSON (StrictSeq a) 
Instance details

Defined in Data.Sequence.Strict

Methods

toJSON :: StrictSeq a -> Value #

toEncoding :: StrictSeq a -> Encoding #

toJSONList :: [StrictSeq a] -> Value #

toEncodingList :: [StrictSeq a] -> Encoding #

omitField :: StrictSeq a -> Bool #

ToJSON a => ToJSON (IntMap a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: IntMap a -> Value #

toEncoding :: IntMap a -> Encoding #

toJSONList :: [IntMap a] -> Value #

toEncodingList :: [IntMap a] -> Encoding #

omitField :: IntMap a -> Bool #

ToJSON a => ToJSON (Seq a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Seq a -> Value #

toEncoding :: Seq a -> Encoding #

toJSONList :: [Seq a] -> Value #

toEncodingList :: [Seq a] -> Encoding #

omitField :: Seq a -> Bool #

ToJSON a => ToJSON (Set a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Set a -> Value #

toEncoding :: Set a -> Encoding #

toJSONList :: [Set a] -> Value #

toEncodingList :: [Set a] -> Encoding #

omitField :: Set a -> Bool #

ToJSON v => ToJSON (Tree v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Tree v -> Value #

toEncoding :: Tree v -> Encoding #

toJSONList :: [Tree v] -> Value #

toEncodingList :: [Tree v] -> Encoding #

omitField :: Tree v -> Bool #

ToJSON1 f => ToJSON (Fix f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Fix f -> Value #

toEncoding :: Fix f -> Encoding #

toJSONList :: [Fix f] -> Value #

toEncodingList :: [Fix f] -> Encoding #

omitField :: Fix f -> Bool #

(ToJSON1 f, Functor f) => ToJSON (Mu f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Mu f -> Value #

toEncoding :: Mu f -> Encoding #

toJSONList :: [Mu f] -> Value #

toEncodingList :: [Mu f] -> Encoding #

omitField :: Mu f -> Bool #

(ToJSON1 f, Functor f) => ToJSON (Nu f) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Nu f -> Value #

toEncoding :: Nu f -> Encoding #

toJSONList :: [Nu f] -> Value #

toEncodingList :: [Nu f] -> Encoding #

omitField :: Nu f -> Bool #

ToJSON a => ToJSON (DNonEmpty a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DNonEmpty a -> Value #

toEncoding :: DNonEmpty a -> Encoding #

toJSONList :: [DNonEmpty a] -> Value #

toEncodingList :: [DNonEmpty a] -> Encoding #

omitField :: DNonEmpty a -> Bool #

ToJSON a => ToJSON (DList a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: DList a -> Value #

toEncoding :: DList a -> Encoding #

toJSONList :: [DList a] -> Value #

toEncodingList :: [DList a] -> Encoding #

omitField :: DList a -> Bool #

ToJSON out => ToJSON (UTxO' out) Source # 
Instance details

Defined in Cardano.Api.UTxO

Methods

toJSON :: UTxO' out -> Value #

toEncoding :: UTxO' out -> Encoding #

toJSONList :: [UTxO' out] -> Value #

toEncodingList :: [UTxO' out] -> Encoding #

omitField :: UTxO' out -> Bool #

ToJSON a => ToJSON (Array a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Array a -> Value #

toEncoding :: Array a -> Encoding #

toJSONList :: [Array a] -> Value #

toEncodingList :: [Array a] -> Encoding #

omitField :: Array a -> Bool #

(Prim a, ToJSON a) => ToJSON (PrimArray a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: PrimArray a -> Value #

toEncoding :: PrimArray a -> Encoding #

toJSONList :: [PrimArray a] -> Value #

toEncodingList :: [PrimArray a] -> Encoding #

omitField :: PrimArray a -> Bool #

ToJSON a => ToJSON (SmallArray a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: SmallArray a -> Value #

toEncoding :: SmallArray a -> Encoding #

toJSONList :: [SmallArray a] -> Value #

toEncodingList :: [SmallArray a] -> Encoding #

omitField :: SmallArray a -> Bool #

ToJSON a => ToJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Maybe a -> Value #

toEncoding :: Maybe a -> Encoding #

toJSONList :: [Maybe a] -> Value #

toEncodingList :: [Maybe a] -> Encoding #

omitField :: Maybe a -> Bool #

ToJSON a => ToJSON (HashSet a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: HashSet a -> Value #

toEncoding :: HashSet a -> Encoding #

toJSONList :: [HashSet a] -> Value #

toEncodingList :: [HashSet a] -> Encoding #

omitField :: HashSet a -> Bool #

ToJSON a => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value #

toEncoding :: Vector a -> Encoding #

toJSONList :: [Vector a] -> Value #

toEncodingList :: [Vector a] -> Encoding #

omitField :: Vector a -> Bool #

(Prim a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value #

toEncoding :: Vector a -> Encoding #

toJSONList :: [Vector a] -> Value #

toEncodingList :: [Vector a] -> Encoding #

omitField :: Vector a -> Bool #

(Storable a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value #

toEncoding :: Vector a -> Encoding #

toJSONList :: [Vector a] -> Value #

toEncodingList :: [Vector a] -> Encoding #

omitField :: Vector a -> Bool #

(Vector Vector a, ToJSON a) => ToJSON (Vector a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Vector a -> Value #

toEncoding :: Vector a -> Encoding #

toJSONList :: [Vector a] -> Value #

toEncodingList :: [Vector a] -> Encoding #

omitField :: Vector a -> Bool #

ToJSON a => ToJSON (Maybe a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Maybe a -> Value #

toEncoding :: Maybe a -> Encoding #

toJSONList :: [Maybe a] -> Value #

toEncodingList :: [Maybe a] -> Encoding #

omitField :: Maybe a -> Bool #

ToJSON a => ToJSON (a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a) -> Value #

toEncoding :: (a) -> Encoding #

toJSONList :: [(a)] -> Value #

toEncodingList :: [(a)] -> Encoding #

omitField :: (a) -> Bool #

ToJSON a => ToJSON [a] 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: [a] -> Value #

toEncoding :: [a] -> Encoding #

toJSONList :: [[a]] -> Value #

toEncodingList :: [[a]] -> Encoding #

omitField :: [a] -> Bool #

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

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Either a b -> Value #

toEncoding :: Either a b -> Encoding #

toJSONList :: [Either a b] -> Value #

toEncodingList :: [Either a b] -> Encoding #

omitField :: Either a b -> Bool #

HasResolution a => ToJSON (Fixed a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Fixed a -> Value #

toEncoding :: Fixed a -> Encoding #

toJSONList :: [Fixed a] -> Value #

toEncodingList :: [Fixed a] -> Encoding #

omitField :: Fixed a -> Bool #

ToJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Proxy a -> Value #

toEncoding :: Proxy a -> Encoding #

toJSONList :: [Proxy a] -> Value #

toEncodingList :: [Proxy a] -> Encoding #

omitField :: Proxy a -> Bool #

ToJSON (File content direction) 
Instance details

Defined in Cardano.Api.IO.Base

Methods

toJSON :: File content direction -> Value #

toEncoding :: File content direction -> Encoding #

toJSONList :: [File content direction] -> Value #

toEncodingList :: [File content direction] -> Encoding #

omitField :: File content direction -> Bool #

ToJSON (ScriptLanguageInEra lang era) 
Instance details

Defined in Cardano.Api.Script

Methods

toJSON :: ScriptLanguageInEra lang era -> Value #

toEncoding :: ScriptLanguageInEra lang era -> Encoding #

toJSONList :: [ScriptLanguageInEra lang era] -> Value #

toEncodingList :: [ScriptLanguageInEra lang era] -> Encoding #

omitField :: ScriptLanguageInEra lang era -> Bool #

IsCardanoEra era => ToJSON (TxOut ctx era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

toJSON :: TxOut ctx era -> Value #

toEncoding :: TxOut ctx era -> Encoding #

toJSONList :: [TxOut ctx era] -> Value #

toEncodingList :: [TxOut ctx era] -> Encoding #

omitField :: TxOut ctx era -> Bool #

HashAlgorithm h => ToJSON (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

toJSON :: Hash h a -> Value #

toEncoding :: Hash h a -> Encoding #

toJSONList :: [Hash h a] -> Value #

toEncodingList :: [Hash h a] -> Encoding #

omitField :: Hash h a -> Bool #

(ToJSON v, ToJSONKey k) => ToJSON (ListMap k v) 
Instance details

Defined in Data.ListMap

Methods

toJSON :: ListMap k v -> Value #

toEncoding :: ListMap k v -> Encoding #

toJSONList :: [ListMap k v] -> Value #

toEncodingList :: [ListMap k v] -> Encoding #

omitField :: ListMap k v -> Bool #

Crypto c => ToJSON (AlonzoPParams Identity (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Methods

toJSON :: AlonzoPParams Identity (AlonzoEra c) -> Value #

toEncoding :: AlonzoPParams Identity (AlonzoEra c) -> Encoding #

toJSONList :: [AlonzoPParams Identity (AlonzoEra c)] -> Value #

toEncodingList :: [AlonzoPParams Identity (AlonzoEra c)] -> Encoding #

omitField :: AlonzoPParams Identity (AlonzoEra c) -> Bool #

Crypto c => ToJSON (AlonzoPParams StrictMaybe (AlonzoEra c)) 
Instance details

Defined in Cardano.Ledger.Alonzo.PParams

Methods

toJSON :: AlonzoPParams StrictMaybe (AlonzoEra c) -> Value #

toEncoding :: AlonzoPParams StrictMaybe (AlonzoEra c) -> Encoding #

toJSONList :: [AlonzoPParams StrictMaybe (AlonzoEra c)] -> Value #

toEncodingList :: [AlonzoPParams StrictMaybe (AlonzoEra c)] -> Encoding #

omitField :: AlonzoPParams StrictMaybe (AlonzoEra c) -> Bool #

(forall a b. (ToJSON a, ToJSON b) => ToJSON (f a b), ToJSON (TxCert era), Era era) => ToJSON (AlonzoPlutusPurpose f era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Methods

toJSON :: AlonzoPlutusPurpose f era -> Value #

toEncoding :: AlonzoPlutusPurpose f era -> Encoding #

toJSONList :: [AlonzoPlutusPurpose f era] -> Value #

toEncodingList :: [AlonzoPlutusPurpose f era] -> Encoding #

omitField :: AlonzoPlutusPurpose f era -> Bool #

ToJSON a => ToJSON (AsIndex a b) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Methods

toJSON :: AsIndex a b -> Value #

toEncoding :: AsIndex a b -> Encoding #

toJSONList :: [AsIndex a b] -> Value #

toEncodingList :: [AsIndex a b] -> Encoding #

omitField :: AsIndex a b -> Bool #

ToJSON b => ToJSON (AsItem a b) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Methods

toJSON :: AsItem a b -> Value #

toEncoding :: AsItem a b -> Encoding #

toJSONList :: [AsItem a b] -> Value #

toEncodingList :: [AsItem a b] -> Encoding #

omitField :: AsItem a b -> Bool #

(PParamsHKD Identity era ~ BabbagePParams Identity era, BabbageEraPParams era, ProtVerAtMost era 8) => ToJSON (BabbagePParams Identity era) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Methods

toJSON :: BabbagePParams Identity era -> Value #

toEncoding :: BabbagePParams Identity era -> Encoding #

toJSONList :: [BabbagePParams Identity era] -> Value #

toEncodingList :: [BabbagePParams Identity era] -> Encoding #

omitField :: BabbagePParams Identity era -> Bool #

(PParamsHKD StrictMaybe era ~ BabbagePParams StrictMaybe era, BabbageEraPParams era, ProtVerAtMost era 8) => ToJSON (BabbagePParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Babbage.PParams

Methods

toJSON :: BabbagePParams StrictMaybe era -> Value #

toEncoding :: BabbagePParams StrictMaybe era -> Encoding #

toJSONList :: [BabbagePParams StrictMaybe era] -> Value #

toEncodingList :: [BabbagePParams StrictMaybe era] -> Encoding #

omitField :: BabbagePParams StrictMaybe era -> Bool #

ToJSON b => ToJSON (Annotated b a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.Annotated

Methods

toJSON :: Annotated b a -> Value #

toEncoding :: Annotated b a -> Encoding #

toJSONList :: [Annotated b a] -> Value #

toEncodingList :: [Annotated b a] -> Encoding #

omitField :: Annotated b a -> Bool #

Era era => ToJSON (GovPurposeId p era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance.Procedures

Methods

toJSON :: GovPurposeId p era -> Value #

toEncoding :: GovPurposeId p era -> Encoding #

toJSONList :: [GovPurposeId p era] -> Value #

toEncodingList :: [GovPurposeId p era] -> Encoding #

omitField :: GovPurposeId p era -> Bool #

Crypto c => ToJSON (ConwayPParams Identity (ConwayEra c)) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

toJSON :: ConwayPParams Identity (ConwayEra c) -> Value #

toEncoding :: ConwayPParams Identity (ConwayEra c) -> Encoding #

toJSONList :: [ConwayPParams Identity (ConwayEra c)] -> Value #

toEncodingList :: [ConwayPParams Identity (ConwayEra c)] -> Encoding #

omitField :: ConwayPParams Identity (ConwayEra c) -> Bool #

(ConwayEraPParams era, PParamsHKD StrictMaybe era ~ ConwayPParams StrictMaybe era) => ToJSON (ConwayPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

toJSON :: ConwayPParams StrictMaybe era -> Value #

toEncoding :: ConwayPParams StrictMaybe era -> Encoding #

toJSONList :: [ConwayPParams StrictMaybe era] -> Value #

toEncodingList :: [ConwayPParams StrictMaybe era] -> Encoding #

omitField :: ConwayPParams StrictMaybe era -> Bool #

(forall a b. (ToJSON a, ToJSON b) => ToJSON (f a b), ToJSON (TxCert era), EraPParams era) => ToJSON (ConwayPlutusPurpose f era) 
Instance details

Defined in Cardano.Ledger.Conway.Scripts

Methods

toJSON :: ConwayPlutusPurpose f era -> Value #

toEncoding :: ConwayPlutusPurpose f era -> Encoding #

toJSONList :: [ConwayPlutusPurpose f era] -> Value #

toEncodingList :: [ConwayPlutusPurpose f era] -> Encoding #

omitField :: ConwayPlutusPurpose f era -> Bool #

ToJSON (BoundedRatio b Word64) 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toJSON :: BoundedRatio b Word64 -> Value #

toEncoding :: BoundedRatio b Word64 -> Encoding #

toJSONList :: [BoundedRatio b Word64] -> Value #

toEncodingList :: [BoundedRatio b Word64] -> Encoding #

omitField :: BoundedRatio b Word64 -> Bool #

Crypto c => ToJSON (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

toJSON :: Credential kr c -> Value #

toEncoding :: Credential kr c -> Encoding #

toJSONList :: [Credential kr c] -> Value #

toEncodingList :: [Credential kr c] -> Encoding #

omitField :: Credential kr c -> Bool #

Crypto c => ToJSON (KeyHash disc c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

toJSON :: KeyHash disc c -> Value #

toEncoding :: KeyHash disc c -> Encoding #

toJSONList :: [KeyHash disc c] -> Value #

toEncodingList :: [KeyHash disc c] -> Encoding #

omitField :: KeyHash disc c -> Bool #

Crypto c => ToJSON (SafeHash c index) 
Instance details

Defined in Cardano.Ledger.SafeHash

Methods

toJSON :: SafeHash c index -> Value #

toEncoding :: SafeHash c index -> Encoding #

toJSONList :: [SafeHash c index] -> Value #

toEncodingList :: [SafeHash c index] -> Encoding #

omitField :: SafeHash c index -> Bool #

(EraPParams era, PParamsHKD Identity era ~ ShelleyPParams Identity era, ProtVerAtMost era 4, ProtVerAtMost era 6, ProtVerAtMost era 8) => ToJSON (ShelleyPParams Identity era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

toJSON :: ShelleyPParams Identity era -> Value #

toEncoding :: ShelleyPParams Identity era -> Encoding #

toJSONList :: [ShelleyPParams Identity era] -> Value #

toEncodingList :: [ShelleyPParams Identity era] -> Encoding #

omitField :: ShelleyPParams Identity era -> Bool #

(EraPParams era, PParamsHKD StrictMaybe era ~ ShelleyPParams StrictMaybe era, ProtVerAtMost era 4, ProtVerAtMost era 6, ProtVerAtMost era 8) => ToJSON (ShelleyPParams StrictMaybe era) 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

toJSON :: ShelleyPParams StrictMaybe era -> Value #

toEncoding :: ShelleyPParams StrictMaybe era -> Encoding #

toJSONList :: [ShelleyPParams StrictMaybe era] -> Value #

toEncodingList :: [ShelleyPParams StrictMaybe era] -> Encoding #

omitField :: ShelleyPParams StrictMaybe era -> Bool #

(ToJSON v, ToJSONKey k) => ToJSON (Map k v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Map k v -> Value #

toEncoding :: Map k v -> Encoding #

toJSONList :: [Map k v] -> Value #

toEncodingList :: [Map k v] -> Encoding #

omitField :: Map k v -> Bool #

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

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Either a b -> Value #

toEncoding :: Either a b -> Encoding #

toJSONList :: [Either a b] -> Value #

toEncodingList :: [Either a b] -> Encoding #

omitField :: Either a b -> Bool #

(ToJSON a, ToJSON b) => ToJSON (These a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: These a b -> Value #

toEncoding :: These a b -> Encoding #

toJSONList :: [These a b] -> Value #

toEncodingList :: [These a b] -> Encoding #

omitField :: These a b -> Bool #

(ToJSON a, ToJSON b) => ToJSON (Pair a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Pair a b -> Value #

toEncoding :: Pair a b -> Encoding #

toJSONList :: [Pair a b] -> Value #

toEncodingList :: [Pair a b] -> Encoding #

omitField :: Pair a b -> Bool #

(ToJSON a, ToJSON b) => ToJSON (These a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: These a b -> Value #

toEncoding :: These a b -> Encoding #

toJSONList :: [These a b] -> Value #

toEncodingList :: [These a b] -> Encoding #

omitField :: These a b -> Bool #

(ToJSON v, ToJSONKey k) => ToJSON (HashMap k v) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: HashMap k v -> Value #

toEncoding :: HashMap k v -> Encoding #

toJSONList :: [HashMap k v] -> Value #

toEncodingList :: [HashMap k v] -> Encoding #

omitField :: HashMap k v -> Bool #

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

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b) -> Value #

toEncoding :: (a, b) -> Encoding #

toJSONList :: [(a, b)] -> Value #

toEncodingList :: [(a, b)] -> Encoding #

omitField :: (a, b) -> Bool #

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

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Const a b -> Value #

toEncoding :: Const a b -> Encoding #

toJSONList :: [Const a b] -> Value #

toEncodingList :: [Const a b] -> Encoding #

omitField :: Const a b -> Bool #

(Typeable t, ToJSON a) => ToJSON (THKD t Identity a) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

toJSON :: THKD t Identity a -> Value #

toEncoding :: THKD t Identity a -> Encoding #

toJSONList :: [THKD t Identity a] -> Value #

toEncodingList :: [THKD t Identity a] -> Encoding #

omitField :: THKD t Identity a -> Bool #

(Typeable t, ToJSON a) => ToJSON (THKD t StrictMaybe a) 
Instance details

Defined in Cardano.Ledger.Conway.PParams

Methods

toJSON :: THKD t StrictMaybe a -> Value #

toEncoding :: THKD t StrictMaybe a -> Encoding #

toJSONList :: [THKD t StrictMaybe a] -> Value #

toEncodingList :: [THKD t StrictMaybe a] -> Encoding #

omitField :: THKD t StrictMaybe a -> Bool #

ToJSON b => ToJSON (Tagged a b) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Tagged a b -> Value #

toEncoding :: Tagged a b -> Encoding #

toJSONList :: [Tagged a b] -> Value #

toEncodingList :: [Tagged a b] -> Encoding #

omitField :: Tagged a b -> Bool #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (These1 f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: These1 f g a -> Value #

toEncoding :: These1 f g a -> Encoding #

toJSONList :: [These1 f g a] -> Value #

toEncodingList :: [These1 f g a] -> Encoding #

omitField :: These1 f g a -> Bool #

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

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c) -> Value #

toEncoding :: (a, b, c) -> Encoding #

toJSONList :: [(a, b, c)] -> Value #

toEncodingList :: [(a, b, c)] -> Encoding #

omitField :: (a, b, c) -> Bool #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Product f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Product f g a -> Value #

toEncoding :: Product f g a -> Encoding #

toJSONList :: [Product f g a] -> Value #

toEncodingList :: [Product f g a] -> Encoding #

omitField :: Product f g a -> Bool #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Sum f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Sum f g a -> Value #

toEncoding :: Sum f g a -> Encoding #

toJSONList :: [Sum f g a] -> Value #

toEncodingList :: [Sum f g a] -> Encoding #

omitField :: Sum f g a -> Bool #

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

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d) -> Value #

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

toJSONList :: [(a, b, c, d)] -> Value #

toEncodingList :: [(a, b, c, d)] -> Encoding #

omitField :: (a, b, c, d) -> Bool #

(ToJSON1 f, ToJSON1 g, ToJSON a) => ToJSON (Compose f g a) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: Compose f g a -> Value #

toEncoding :: Compose f g a -> Encoding #

toJSONList :: [Compose f g a] -> Value #

toEncodingList :: [Compose f g a] -> Encoding #

omitField :: Compose f g a -> Bool #

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

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e) -> Value #

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

toJSONList :: [(a, b, c, d, e)] -> Value #

toEncodingList :: [(a, b, c, d, e)] -> Encoding #

omitField :: (a, b, c, d, e) -> Bool #

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

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f) -> Value #

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

toJSONList :: [(a, b, c, d, e, f)] -> Value #

toEncodingList :: [(a, b, c, d, e, f)] -> Encoding #

omitField :: (a, b, c, d, e, f) -> Bool #

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

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g) -> Value #

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

toJSONList :: [(a, b, c, d, e, f, g)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g)] -> Encoding #

omitField :: (a, b, c, d, e, f, g) -> Bool #

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

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h) -> Value #

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

toJSONList :: [(a, b, c, d, e, f, g, h)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i) => ToJSON (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i) -> Value #

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

toJSONList :: [(a, b, c, d, e, f, g, h, i)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j) => ToJSON (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i, j) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k) => ToJSON (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i, j, k) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i, j, k, l) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n) -> Bool #

(ToJSON a, ToJSON b, ToJSON c, ToJSON d, ToJSON e, ToJSON f, ToJSON g, ToJSON h, ToJSON i, ToJSON j, ToJSON k, ToJSON l, ToJSON m, ToJSON n, ToJSON o) => ToJSON (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Data.Aeson.Types.ToJSON

Methods

toJSON :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Value #

toEncoding :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Encoding #

toJSONList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Value #

toEncodingList :: [(a, b, c, d, e, f, g, h, i, j, k, l, m, n, o)] -> Encoding #

omitField :: (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) -> Bool #

class Typeable a => FromCBOR a #

Minimal complete definition

fromCBOR

Instances

Instances details
FromCBOR Void 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Void

label :: Proxy Void -> Text

FromCBOR Int32 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Int32

label :: Proxy Int32 -> Text

FromCBOR Int64 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Int64

label :: Proxy Int64 -> Text

FromCBOR Rational 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Rational

label :: Proxy Rational -> Text

FromCBOR Word16 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Word16

label :: Proxy Word16 -> Text

FromCBOR Word32 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Word32

label :: Proxy Word32 -> Text

FromCBOR Word64 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Word64

label :: Proxy Word64 -> Text

FromCBOR Word8 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Word8

label :: Proxy Word8 -> Text

FromCBOR ByteString 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s ByteString

label :: Proxy ByteString -> Text

FromCBOR ByteString 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s ByteString

label :: Proxy ByteString -> Text

FromCBOR ShortByteString 
Instance details

Defined in Cardano.Binary.FromCBOR

FromCBOR OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

FromCBOR OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

FromCBOR CostModel 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

fromCBOR :: Decoder s CostModel

label :: Proxy CostModel -> Text

FromCBOR ExecutionUnitPrices 
Instance details

Defined in Cardano.Api.ProtocolParameters

FromCBOR PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

fromCBOR :: Decoder s PraosNonce

label :: Proxy PraosNonce -> Text

FromCBOR ProtocolParametersUpdate 
Instance details

Defined in Cardano.Api.ProtocolParameters

FromCBOR UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

FromCBOR AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

FromCBOR ExecutionUnits 
Instance details

Defined in Cardano.Api.Script

FromCBOR ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

Methods

fromCBOR :: Decoder s ScriptData

label :: Proxy ScriptData -> Text

FromCBOR TxId Source # 
Instance details

Defined in Hydra.Cardano.Api.TxId

Methods

fromCBOR :: Decoder s TxId

label :: Proxy TxId -> Text

FromCBOR Proof 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

fromCBOR :: Decoder s Proof

label :: Proxy Proof -> Text

FromCBOR SignKey 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

fromCBOR :: Decoder s SignKey

label :: Proxy SignKey -> Text

FromCBOR VerKey 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

fromCBOR :: Decoder s VerKey

label :: Proxy VerKey -> Text

FromCBOR ProtocolMagicId 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Methods

fromCBOR :: Decoder s ProtocolMagicId

label :: Proxy ProtocolMagicId -> Text

FromCBOR RequiresNetworkMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Methods

fromCBOR :: Decoder s RequiresNetworkMagic

label :: Proxy RequiresNetworkMagic -> Text

FromCBOR RedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.VerificationKey

Methods

fromCBOR :: Decoder s RedeemVerificationKey

label :: Proxy RedeemVerificationKey -> Text

FromCBOR SigningKey 
Instance details

Defined in Cardano.Crypto.Signing.SigningKey

Methods

fromCBOR :: Decoder s SigningKey

label :: Proxy SigningKey -> Text

FromCBOR VerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

Methods

fromCBOR :: Decoder s VerificationKey

label :: Proxy VerificationKey -> Text

FromCBOR AlonzoGenesis 
Instance details

Defined in Cardano.Ledger.Alonzo.Genesis

Methods

fromCBOR :: Decoder s AlonzoGenesis

label :: Proxy AlonzoGenesis -> Text

FromCBOR Version 
Instance details

Defined in Cardano.Ledger.Binary.Version

Methods

fromCBOR :: Decoder s Version

label :: Proxy Version -> Text

FromCBOR HDAddressPayload 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

Methods

fromCBOR :: Decoder s HDAddressPayload

label :: Proxy HDAddressPayload -> Text

FromCBOR AddrSpendingData 
Instance details

Defined in Cardano.Chain.Common.AddrSpendingData

Methods

fromCBOR :: Decoder s AddrSpendingData

label :: Proxy AddrSpendingData -> Text

FromCBOR AddrType 
Instance details

Defined in Cardano.Chain.Common.AddrSpendingData

Methods

fromCBOR :: Decoder s AddrType

label :: Proxy AddrType -> Text

FromCBOR Address 
Instance details

Defined in Cardano.Chain.Common.Address

Methods

fromCBOR :: Decoder s Address

label :: Proxy Address -> Text

FromCBOR Address' 
Instance details

Defined in Cardano.Chain.Common.Address

Methods

fromCBOR :: Decoder s Address'

label :: Proxy Address' -> Text

FromCBOR NetworkMagic 
Instance details

Defined in Cardano.Chain.Common.NetworkMagic

Methods

fromCBOR :: Decoder s NetworkMagic

label :: Proxy NetworkMagic -> Text

FromCBOR Config 
Instance details

Defined in Cardano.Chain.Genesis.Config

Methods

fromCBOR :: Decoder s Config

label :: Proxy Config -> Text

FromCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Methods

fromCBOR :: Decoder s EpochSlots

label :: Proxy EpochSlots -> Text

FromCBOR Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

fromCBOR :: Decoder s Tx

label :: Proxy Tx -> Text

FromCBOR TxIn 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

fromCBOR :: Decoder s TxIn

label :: Proxy TxIn -> Text

FromCBOR TxOut 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

fromCBOR :: Decoder s TxOut

label :: Proxy TxOut -> Text

FromCBOR TxAux 
Instance details

Defined in Cardano.Chain.UTxO.TxAux

Methods

fromCBOR :: Decoder s TxAux

label :: Proxy TxAux -> Text

FromCBOR TxInWitness 
Instance details

Defined in Cardano.Chain.UTxO.TxWitness

Methods

fromCBOR :: Decoder s TxInWitness

label :: Proxy TxInWitness -> Text

FromCBOR TxSigData 
Instance details

Defined in Cardano.Chain.UTxO.TxWitness

Methods

fromCBOR :: Decoder s TxSigData

label :: Proxy TxSigData -> Text

FromCBOR ProtocolVersion 
Instance details

Defined in Cardano.Chain.Update.ProtocolVersion

Methods

fromCBOR :: Decoder s ProtocolVersion

label :: Proxy ProtocolVersion -> Text

FromCBOR Adopted 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

fromCBOR :: Decoder s Adopted

label :: Proxy Adopted -> Text

FromCBOR ApplicationVersion 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

fromCBOR :: Decoder s ApplicationVersion

label :: Proxy ApplicationVersion -> Text

FromCBOR Error 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

fromCBOR :: Decoder s Error

label :: Proxy Error -> Text

FromCBOR ProtocolUpdateProposal 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

fromCBOR :: Decoder s ProtocolUpdateProposal

label :: Proxy ProtocolUpdateProposal -> Text

FromCBOR SoftwareUpdateProposal 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

fromCBOR :: Decoder s SoftwareUpdateProposal

label :: Proxy SoftwareUpdateProposal -> Text

FromCBOR CertIx 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

fromCBOR :: Decoder s CertIx

label :: Proxy CertIx -> Text

FromCBOR EpochInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

fromCBOR :: Decoder s EpochInterval

label :: Proxy EpochInterval -> Text

FromCBOR Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

fromCBOR :: Decoder s Nonce

label :: Proxy Nonce -> Text

FromCBOR ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

fromCBOR :: Decoder s ProtVer

label :: Proxy ProtVer -> Text

FromCBOR TxIx 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

fromCBOR :: Decoder s TxIx

label :: Proxy TxIx -> Text

FromCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

fromCBOR :: Decoder s Coin

label :: Proxy Coin -> Text

FromCBOR Ptr 
Instance details

Defined in Cardano.Ledger.Credential

Methods

fromCBOR :: Decoder s Ptr

label :: Proxy Ptr -> Text

FromCBOR Language 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

fromCBOR :: Decoder s Language

label :: Proxy Language -> Text

FromCBOR PlutusBinary 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

fromCBOR :: Decoder s PlutusBinary

label :: Proxy PlutusBinary -> Text

FromCBOR KESPeriod 
Instance details

Defined in Cardano.Protocol.TPraos.OCert

Methods

fromCBOR :: Decoder s KESPeriod

label :: Proxy KESPeriod -> Text

FromCBOR BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

fromCBOR :: Decoder s BlockNo

label :: Proxy BlockNo -> Text

FromCBOR EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

fromCBOR :: Decoder s EpochNo

label :: Proxy EpochNo -> Text

FromCBOR EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Methods

fromCBOR :: Decoder s EpochSize

label :: Proxy EpochSize -> Text

FromCBOR SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

fromCBOR :: Decoder s SlotNo

label :: Proxy SlotNo -> Text

FromCBOR RelativeTime 
Instance details

Defined in Cardano.Slotting.Time

Methods

fromCBOR :: Decoder s RelativeTime

label :: Proxy RelativeTime -> Text

FromCBOR SlotLength 
Instance details

Defined in Cardano.Slotting.Time

Methods

fromCBOR :: Decoder s SlotLength

label :: Proxy SlotLength -> Text

FromCBOR SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

fromCBOR :: Decoder s SystemStart

label :: Proxy SystemStart -> Text

FromCBOR TermToken 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s TermToken

label :: Proxy TermToken -> Text

FromCBOR Term 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Term

label :: Proxy Term -> Text

FromCBOR Text 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Text

label :: Proxy Text -> Text

FromCBOR UTCTime 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s UTCTime

label :: Proxy UTCTime -> Text

FromCBOR Integer 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Integer

label :: Proxy Integer -> Text

FromCBOR Natural 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Natural

label :: Proxy Natural -> Text

FromCBOR () 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s ()

label :: Proxy () -> Text

FromCBOR Bool 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Bool

label :: Proxy Bool -> Text

FromCBOR Double 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Double

label :: Proxy Double -> Text

FromCBOR Float 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Float

label :: Proxy Float -> Text

FromCBOR Int 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Int

label :: Proxy Int -> Text

FromCBOR Word 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s Word

label :: Proxy Word -> Text

FromCBOR a => FromCBOR (NonEmpty a) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (NonEmpty a)

label :: Proxy (NonEmpty a) -> Text

IsShelleyBasedEra era => FromCBOR (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

Methods

fromCBOR :: Decoder s (Certificate era)

label :: Proxy (Certificate era) -> Text

IsShelleyBasedEra era => FromCBOR (Proposal era) 
Instance details

Defined in Cardano.Api.Governance.Actions.ProposalProcedure

Methods

fromCBOR :: Decoder s (Proposal era)

label :: Proxy (Proposal era) -> Text

IsShelleyBasedEra era => FromCBOR (GovernanceActionId era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

Methods

fromCBOR :: Decoder s (GovernanceActionId era)

label :: Proxy (GovernanceActionId era) -> Text

IsShelleyBasedEra era => FromCBOR (Voter era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

Methods

fromCBOR :: Decoder s (Voter era)

label :: Proxy (Voter era) -> Text

IsShelleyBasedEra era => FromCBOR (VotingProcedure era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

Methods

fromCBOR :: Decoder s (VotingProcedure era)

label :: Proxy (VotingProcedure era) -> Text

IsShelleyBasedEra era => FromCBOR (VotingProcedures era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

Methods

fromCBOR :: Decoder s (VotingProcedures era)

label :: Proxy (VotingProcedures era) -> Text

FromCBOR (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

fromCBOR :: Decoder s (Hash ByronKey)

label :: Proxy (Hash ByronKey) -> Text

FromCBOR (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (Hash KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

fromCBOR :: Decoder s (Hash KesKey)

label :: Proxy (Hash KesKey) -> Text

FromCBOR (Hash VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

fromCBOR :: Decoder s (Hash VrfKey)

label :: Proxy (Hash VrfKey) -> Text

FromCBOR (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash DRepKey)

label :: Proxy (Hash DRepKey) -> Text

FromCBOR (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash GenesisKey)

label :: Proxy (Hash GenesisKey) -> Text

FromCBOR (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash PaymentKey)

label :: Proxy (Hash PaymentKey) -> Text

FromCBOR (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash StakeKey)

label :: Proxy (Hash StakeKey) -> Text

FromCBOR (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash StakePoolKey)

label :: Proxy (Hash StakePoolKey) -> Text

FromCBOR (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

fromCBOR :: Decoder s (SigningKey KesKey)

label :: Proxy (SigningKey KesKey) -> Text

FromCBOR (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

fromCBOR :: Decoder s (SigningKey VrfKey)

label :: Proxy (SigningKey VrfKey) -> Text

FromCBOR (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

FromCBOR (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

FromCBOR (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsShelleyBasedEra era => FromCBOR (DebugLedgerState era) 
Instance details

Defined in Cardano.Api.Query.Types

Methods

fromCBOR :: Decoder s (DebugLedgerState era)

label :: Proxy (DebugLedgerState era) -> Text

HasTypeProxy lang => FromCBOR (PlutusScript lang) 
Instance details

Defined in Cardano.Api.Script

Methods

fromCBOR :: Decoder s (PlutusScript lang)

label :: Proxy (PlutusScript lang) -> Text

SerialiseAsRawBytes a => FromCBOR (UsingRawBytes a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

fromCBOR :: Decoder s (UsingRawBytes a)

label :: Proxy (UsingRawBytes a) -> Text

FromCBOR (SigDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Methods

fromCBOR :: Decoder s (SigDSIGN Ed25519DSIGN)

label :: Proxy (SigDSIGN Ed25519DSIGN) -> Text

FromCBOR (SignKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Methods

fromCBOR :: Decoder s (SignKeyDSIGN Ed25519DSIGN)

label :: Proxy (SignKeyDSIGN Ed25519DSIGN) -> Text

FromCBOR (VerKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Methods

fromCBOR :: Decoder s (VerKeyDSIGN Ed25519DSIGN)

label :: Proxy (VerKeyDSIGN Ed25519DSIGN) -> Text

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

Defined in Cardano.Crypto.KES.Single

Methods

fromCBOR :: Decoder s (SigKES (SingleKES d))

label :: Proxy (SigKES (SingleKES d)) -> Text

(KESAlgorithm d, HashAlgorithm h) => FromCBOR (SigKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

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

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

DSIGNAlgorithm d => FromCBOR (SignKeyKES (SingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

fromCBOR :: Decoder s (SignKeyKES (SingleKES d))

label :: Proxy (SignKeyKES (SingleKES d)) -> Text

(KESAlgorithm d, HashAlgorithm h) => FromCBOR (SignKeyKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

fromCBOR :: Decoder s (SignKeyKES (SumKES h d))

label :: Proxy (SignKeyKES (SumKES h d)) -> Text

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

Defined in Cardano.Crypto.KES.Single

Methods

fromCBOR :: Decoder s (VerKeyKES (SingleKES d))

label :: Proxy (VerKeyKES (SingleKES d)) -> Text

(KESAlgorithm d, HashAlgorithm h) => FromCBOR (VerKeyKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

fromCBOR :: Decoder s (VerKeyKES (SumKES h d))

label :: Proxy (VerKeyKES (SumKES h d)) -> Text

FromCBOR (CertVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

fromCBOR :: Decoder s (CertVRF PraosVRF)

label :: Proxy (CertVRF PraosVRF) -> Text

Typeable v => FromCBOR (OutputVRF v) 
Instance details

Defined in Cardano.Crypto.VRF.Class

Methods

fromCBOR :: Decoder s (OutputVRF v)

label :: Proxy (OutputVRF v) -> Text

FromCBOR (SignKeyVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

fromCBOR :: Decoder s (SignKeyVRF PraosVRF)

label :: Proxy (SignKeyVRF PraosVRF) -> Text

FromCBOR (VerKeyVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

fromCBOR :: Decoder s (VerKeyVRF PraosVRF)

label :: Proxy (VerKeyVRF PraosVRF) -> Text

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

Defined in Cardano.Ledger.Alonzo.TxOut

Methods

fromCBOR :: Decoder s (AlonzoTxOut era)

label :: Proxy (AlonzoTxOut era) -> Text

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

Defined in Cardano.Ledger.Babbage.TxOut

Methods

fromCBOR :: Decoder s (BabbageTxOut era)

label :: Proxy (BabbageTxOut era) -> Text

FromCBOR (Attributes AddrAttributes) 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

Methods

fromCBOR :: Decoder s (Attributes AddrAttributes)

label :: Proxy (Attributes AddrAttributes) -> Text

FromCBOR (ATxAux ByteSpan) 
Instance details

Defined in Cardano.Chain.UTxO.TxAux

Methods

fromCBOR :: Decoder s (ATxAux ByteSpan)

label :: Proxy (ATxAux ByteSpan) -> Text

DecCBOR n => FromCBOR (TooLarge n) 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

fromCBOR :: Decoder s (TooLarge n)

label :: Proxy (TooLarge n) -> Text

EraPParams era => FromCBOR (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

fromCBOR :: Decoder s (ConwayGovState era)

label :: Proxy (ConwayGovState era) -> Text

EraPParams era => FromCBOR (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

fromCBOR :: Decoder s (EnactState era)

label :: Proxy (EnactState era) -> Text

EraPParams era => FromCBOR (PulsingSnapshot era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

fromCBOR :: Decoder s (PulsingSnapshot era)

label :: Proxy (PulsingSnapshot era) -> Text

EraPParams era => FromCBOR (ConwayGovPredFailure era) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Gov

Methods

fromCBOR :: Decoder s (ConwayGovPredFailure era)

label :: Proxy (ConwayGovPredFailure era) -> Text

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

Defined in Cardano.Ledger.Conway.TxCert

Methods

fromCBOR :: Decoder s (ConwayTxCert era)

label :: Proxy (ConwayTxCert era) -> Text

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

Defined in Cardano.Ledger.Core.PParams

Methods

fromCBOR :: Decoder s (PParams era)

label :: Proxy (PParams era) -> Text

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

Defined in Cardano.Ledger.Core.PParams

Methods

fromCBOR :: Decoder s (PParamsUpdate era)

label :: Proxy (PParamsUpdate era) -> Text

Crypto c => FromCBOR (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

fromCBOR :: Decoder s (ScriptHash c)

label :: Proxy (ScriptHash c) -> Text

PlutusLanguage l => FromCBOR (SLanguage l) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

fromCBOR :: Decoder s (SLanguage l)

label :: Proxy (SLanguage l) -> Text

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

Defined in Cardano.Ledger.UTxO

Methods

fromCBOR :: Decoder s (UTxO era)

label :: Proxy (UTxO era) -> Text

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

Defined in Cardano.Ledger.Shelley.API.Mempool

Methods

fromCBOR :: Decoder s (ApplyTxError era)

label :: Proxy (ApplyTxError era) -> Text

Crypto c => FromCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

fromCBOR :: Decoder s (ShelleyGenesis c)

label :: Proxy (ShelleyGenesis c) -> Text

Era era => FromCBOR (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

fromCBOR :: Decoder s (Constitution era)

label :: Proxy (Constitution era) -> Text

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

Defined in Cardano.Ledger.Shelley.Governance

Methods

fromCBOR :: Decoder s (ShelleyGovState era)

label :: Proxy (ShelleyGovState era) -> Text

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

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

fromCBOR :: Decoder s (EpochState era)

label :: Proxy (EpochState era) -> Text

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

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

fromCBOR :: Decoder s (LedgerState era)

label :: Proxy (LedgerState era) -> Text

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

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

fromCBOR :: Decoder s (NewEpochState era)

label :: Proxy (NewEpochState era) -> Text

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

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

fromCBOR :: Decoder s (UTxOState era)

label :: Proxy (UTxOState era) -> Text

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

Defined in Cardano.Ledger.Shelley.PParams

Methods

fromCBOR :: Decoder s (ProposedPPUpdates era)

label :: Proxy (ProposedPPUpdates era) -> Text

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

Defined in Cardano.Ledger.Shelley.TxCert

Methods

fromCBOR :: Decoder s (ShelleyTxCert era)

label :: Proxy (ShelleyTxCert era) -> Text

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

Defined in Cardano.Ledger.Shelley.TxOut

Methods

fromCBOR :: Decoder s (ShelleyTxOut era)

label :: Proxy (ShelleyTxOut era) -> Text

Crypto c => FromCBOR (ChainDepState c) 
Instance details

Defined in Cardano.Protocol.TPraos.API

Methods

fromCBOR :: Decoder s (ChainDepState c)

label :: Proxy (ChainDepState c) -> Text

Crypto c => FromCBOR (OCert c) 
Instance details

Defined in Cardano.Protocol.TPraos.OCert

Methods

fromCBOR :: Decoder s (OCert c)

label :: Proxy (OCert c) -> Text

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

Defined in Cardano.Slotting.Slot

Methods

fromCBOR :: Decoder s (WithOrigin t)

label :: Proxy (WithOrigin t) -> Text

FromCBOR a => FromCBOR (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Methods

fromCBOR :: Decoder s (StrictMaybe a)

label :: Proxy (StrictMaybe a) -> Text

FromCBOR a => FromCBOR (StrictSeq a) 
Instance details

Defined in Data.Sequence.Strict

Methods

fromCBOR :: Decoder s (StrictSeq a)

label :: Proxy (StrictSeq a) -> Text

FromCBOR a => FromCBOR (Seq a) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Seq a)

label :: Proxy (Seq a) -> Text

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

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Set a)

label :: Proxy (Set a) -> Text

Crypto c => FromCBOR (CompactGenesis c) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

fromCBOR :: Decoder s (CompactGenesis c)

label :: Proxy (CompactGenesis c) -> Text

Crypto c => FromCBOR (NonMyopicMemberRewards c) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBOR :: Decoder s (NonMyopicMemberRewards c)

label :: Proxy (NonMyopicMemberRewards c) -> Text

Crypto crypto => FromCBOR (StakeSnapshot crypto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBOR :: Decoder s (StakeSnapshot crypto)

label :: Proxy (StakeSnapshot crypto) -> Text

Crypto crypto => FromCBOR (StakeSnapshots crypto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

fromCBOR :: Decoder s (StakeSnapshots crypto)

label :: Proxy (StakeSnapshots crypto) -> Text

Crypto c => FromCBOR (LegacyPParams (AllegraEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query.PParamsLegacyEncoder

Methods

fromCBOR :: Decoder s (LegacyPParams (AllegraEra c))

label :: Proxy (LegacyPParams (AllegraEra c)) -> Text

Crypto c => FromCBOR (LegacyPParams (AlonzoEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query.PParamsLegacyEncoder

Methods

fromCBOR :: Decoder s (LegacyPParams (AlonzoEra c))

label :: Proxy (LegacyPParams (AlonzoEra c)) -> Text

Crypto c => FromCBOR (LegacyPParams (BabbageEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query.PParamsLegacyEncoder

Methods

fromCBOR :: Decoder s (LegacyPParams (BabbageEra c))

label :: Proxy (LegacyPParams (BabbageEra c)) -> Text

Crypto c => FromCBOR (LegacyPParams (ConwayEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query.PParamsLegacyEncoder

Methods

fromCBOR :: Decoder s (LegacyPParams (ConwayEra c))

label :: Proxy (LegacyPParams (ConwayEra c)) -> Text

Crypto c => FromCBOR (LegacyPParams (MaryEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query.PParamsLegacyEncoder

Methods

fromCBOR :: Decoder s (LegacyPParams (MaryEra c))

label :: Proxy (LegacyPParams (MaryEra c)) -> Text

Crypto c => FromCBOR (LegacyPParams (ShelleyEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query.PParamsLegacyEncoder

Methods

fromCBOR :: Decoder s (LegacyPParams (ShelleyEra c))

label :: Proxy (LegacyPParams (ShelleyEra c)) -> Text

Crypto crypto => FromCBOR (ShelleyHash crypto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

fromCBOR :: Decoder s (ShelleyHash crypto)

label :: Proxy (ShelleyHash crypto) -> Text

PraosCrypto c => FromCBOR (PraosState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

fromCBOR :: Decoder s (PraosState c)

label :: Proxy (PraosState c) -> Text

PraosCrypto c => FromCBOR (TPraosState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Methods

fromCBOR :: Decoder s (TPraosState c)

label :: Proxy (TPraosState c) -> Text

FromCBOR a => FromCBOR (Vector a) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Vector a)

label :: Proxy (Vector a) -> Text

FromCBOR a => FromCBOR (Maybe a) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Maybe a)

label :: Proxy (Maybe a) -> Text

FromCBOR a => FromCBOR [a] 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s [a]

label :: Proxy [a] -> Text

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

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Either a b)

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

Typeable a => FromCBOR (Fixed a) 
Instance details

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Fixed a)

label :: Proxy (Fixed a) -> Text

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

Defined in Cardano.Crypto.Hash.Class

Methods

fromCBOR :: Decoder s (Hash h a)

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

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

Defined in Cardano.Crypto.VRF.Class

Methods

fromCBOR :: Decoder s (CertifiedVRF v a)

label :: Proxy (CertifiedVRF v a) -> Text

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

Defined in Cardano.Ledger.Alonzo.PParams

Methods

fromCBOR :: Decoder s (AlonzoPParams Identity era)

label :: Proxy (AlonzoPParams Identity era) -> Text

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

Defined in Cardano.Ledger.Alonzo.PParams

Methods

fromCBOR :: Decoder s (AlonzoPParams StrictMaybe era)

label :: Proxy (AlonzoPParams StrictMaybe era) -> Text

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

Defined in Cardano.Ledger.Babbage.PParams

Methods

fromCBOR :: Decoder s (BabbagePParams Identity era)

label :: Proxy (BabbagePParams Identity era) -> Text

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

Defined in Cardano.Ledger.Babbage.PParams

Methods

fromCBOR :: Decoder s (BabbagePParams StrictMaybe era)

label :: Proxy (BabbagePParams StrictMaybe era) -> Text

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

Defined in Cardano.Ledger.Conway.PParams

Methods

fromCBOR :: Decoder s (ConwayPParams Identity era)

label :: Proxy (ConwayPParams Identity era) -> Text

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

Defined in Cardano.Ledger.Conway.PParams

Methods

fromCBOR :: Decoder s (ConwayPParams StrictMaybe era)

label :: Proxy (ConwayPParams StrictMaybe era) -> Text

(Typeable kr, Crypto c) => FromCBOR (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

fromCBOR :: Decoder s (Credential kr c)

label :: Proxy (Credential kr c) -> Text

(Crypto c, Typeable disc) => FromCBOR (KeyHash disc c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

fromCBOR :: Decoder s (KeyHash disc c)

label :: Proxy (KeyHash disc c) -> Text

(Crypto c, Typeable kd) => FromCBOR (VKey kd c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

fromCBOR :: Decoder s (VKey kd c)

label :: Proxy (VKey kd c) -> Text

(Typeable index, Crypto c) => FromCBOR (SafeHash c index) 
Instance details

Defined in Cardano.Ledger.SafeHash

Methods

fromCBOR :: Decoder s (SafeHash c index)

label :: Proxy (SafeHash c index) -> Text

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

Defined in Cardano.Ledger.Shelley.PParams

Methods

fromCBOR :: Decoder s (ShelleyPParams Identity era)

label :: Proxy (ShelleyPParams Identity era) -> Text

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

Defined in Cardano.Ledger.Shelley.PParams

Methods

fromCBOR :: Decoder s (ShelleyPParams StrictMaybe era)

label :: Proxy (ShelleyPParams StrictMaybe era) -> Text

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

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (Map k v)

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

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

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s (a, b)

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

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

Defined in Cardano.Binary.FromCBOR

Methods

fromCBOR :: Decoder s0 (Tagged s a)

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

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

Defined in Cardano.Binary.FromCBOR

Methods

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

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

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

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

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

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

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

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

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

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

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

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

class Typeable a => ToCBOR a #

Minimal complete definition

toCBOR

Instances

Instances details
ToCBOR Void 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Void -> Encoding

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

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

ToCBOR Int32 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Int32 -> Encoding

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

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

ToCBOR Int64 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Int64 -> Encoding

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

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

ToCBOR Word16 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Word16 -> Encoding

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

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

ToCBOR Word32 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Word32 -> Encoding

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

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

ToCBOR Word64 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Word64 -> Encoding

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

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

ToCBOR Word8 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Word8 -> Encoding

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

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

ToCBOR ByteString 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: ByteString -> Encoding

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

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

ToCBOR ByteString 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: ByteString -> Encoding

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

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

ToCBOR ShortByteString 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: ShortByteString -> Encoding

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

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

ToCBOR OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

Methods

toCBOR :: OperationalCertificate -> Encoding

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

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

ToCBOR OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

ToCBOR CostModel 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toCBOR :: CostModel -> Encoding

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

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

ToCBOR ExecutionUnitPrices 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toCBOR :: ExecutionUnitPrices -> Encoding

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

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

ToCBOR PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toCBOR :: PraosNonce -> Encoding

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

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

ToCBOR ProtocolParametersUpdate 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toCBOR :: ProtocolParametersUpdate -> Encoding

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

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

ToCBOR UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toCBOR :: UpdateProposal -> Encoding

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

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

ToCBOR AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

Methods

toCBOR :: AnyPlutusScriptVersion -> Encoding

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

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

ToCBOR ExecutionUnits 
Instance details

Defined in Cardano.Api.Script

Methods

toCBOR :: ExecutionUnits -> Encoding

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

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

ToCBOR ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

Methods

toCBOR :: ScriptData -> Encoding

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

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

ToCBOR TxId Source # 
Instance details

Defined in Hydra.Cardano.Api.TxId

Methods

toCBOR :: TxId -> Encoding

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

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

ToCBOR Proof 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

toCBOR :: Proof -> Encoding

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

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

ToCBOR SignKey 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

toCBOR :: SignKey -> Encoding

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

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

ToCBOR VerKey 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

toCBOR :: VerKey -> Encoding

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

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

ToCBOR ProtocolMagicId 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Methods

toCBOR :: ProtocolMagicId -> Encoding

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

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

ToCBOR RequiresNetworkMagic 
Instance details

Defined in Cardano.Crypto.ProtocolMagic

Methods

toCBOR :: RequiresNetworkMagic -> Encoding

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

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

ToCBOR RedeemVerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.Redeem.VerificationKey

Methods

toCBOR :: RedeemVerificationKey -> Encoding

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

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

ToCBOR SigningKey 
Instance details

Defined in Cardano.Crypto.Signing.SigningKey

Methods

toCBOR :: SigningKey -> Encoding

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

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

ToCBOR VerificationKey 
Instance details

Defined in Cardano.Crypto.Signing.VerificationKey

Methods

toCBOR :: VerificationKey -> Encoding

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

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

ToCBOR AlonzoGenesis 
Instance details

Defined in Cardano.Ledger.Alonzo.Genesis

Methods

toCBOR :: AlonzoGenesis -> Encoding

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

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

ToCBOR IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Methods

toCBOR :: IsValid -> Encoding

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

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

ToCBOR Version 
Instance details

Defined in Cardano.Ledger.Binary.Version

Methods

toCBOR :: Version -> Encoding

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

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

ToCBOR HDAddressPayload 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

Methods

toCBOR :: HDAddressPayload -> Encoding

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

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

ToCBOR AddrSpendingData 
Instance details

Defined in Cardano.Chain.Common.AddrSpendingData

Methods

toCBOR :: AddrSpendingData -> Encoding

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

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

ToCBOR AddrType 
Instance details

Defined in Cardano.Chain.Common.AddrSpendingData

Methods

toCBOR :: AddrType -> Encoding

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

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

ToCBOR Address 
Instance details

Defined in Cardano.Chain.Common.Address

Methods

toCBOR :: Address -> Encoding

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

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

ToCBOR Address' 
Instance details

Defined in Cardano.Chain.Common.Address

Methods

toCBOR :: Address' -> Encoding

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

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

ToCBOR NetworkMagic 
Instance details

Defined in Cardano.Chain.Common.NetworkMagic

Methods

toCBOR :: NetworkMagic -> Encoding

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

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

ToCBOR Config 
Instance details

Defined in Cardano.Chain.Genesis.Config

Methods

toCBOR :: Config -> Encoding

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

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

ToCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Methods

toCBOR :: EpochSlots -> Encoding

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

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

ToCBOR Tx 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

toCBOR :: Tx -> Encoding

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

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

ToCBOR TxIn 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

toCBOR :: TxIn -> Encoding

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

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

ToCBOR TxOut 
Instance details

Defined in Cardano.Chain.UTxO.Tx

Methods

toCBOR :: TxOut -> Encoding

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

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

ToCBOR TxAux 
Instance details

Defined in Cardano.Chain.UTxO.TxAux

Methods

toCBOR :: TxAux -> Encoding

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

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

ToCBOR TxInWitness 
Instance details

Defined in Cardano.Chain.UTxO.TxWitness

Methods

toCBOR :: TxInWitness -> Encoding

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

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

ToCBOR TxSigData 
Instance details

Defined in Cardano.Chain.UTxO.TxWitness

Methods

toCBOR :: TxSigData -> Encoding

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

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

ToCBOR ProtocolVersion 
Instance details

Defined in Cardano.Chain.Update.ProtocolVersion

Methods

toCBOR :: ProtocolVersion -> Encoding

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

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

ToCBOR Adopted 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

toCBOR :: Adopted -> Encoding

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

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

ToCBOR ApplicationVersion 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

toCBOR :: ApplicationVersion -> Encoding

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

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

ToCBOR Error 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

toCBOR :: Error -> Encoding

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

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

ToCBOR ProtocolUpdateProposal 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

toCBOR :: ProtocolUpdateProposal -> Encoding

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

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

ToCBOR SoftwareUpdateProposal 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

toCBOR :: SoftwareUpdateProposal -> Encoding

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

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

ToCBOR CertIx 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: CertIx -> Encoding

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

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

ToCBOR EpochInterval 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: EpochInterval -> Encoding

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

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

ToCBOR Nonce 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: Nonce -> Encoding

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

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

ToCBOR ProtVer 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: ProtVer -> Encoding

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

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

ToCBOR TxIx 
Instance details

Defined in Cardano.Ledger.BaseTypes

Methods

toCBOR :: TxIx -> Encoding

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

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

ToCBOR Coin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toCBOR :: Coin -> Encoding

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

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

ToCBOR DeltaCoin 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toCBOR :: DeltaCoin -> Encoding

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

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

ToCBOR Ptr 
Instance details

Defined in Cardano.Ledger.Credential

Methods

toCBOR :: Ptr -> Encoding

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

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

ToCBOR Language 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

toCBOR :: Language -> Encoding

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

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

ToCBOR PlutusBinary 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

toCBOR :: PlutusBinary -> Encoding

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

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

ToCBOR KESPeriod 
Instance details

Defined in Cardano.Protocol.TPraos.OCert

Methods

toCBOR :: KESPeriod -> Encoding

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

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

ToCBOR BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

toCBOR :: BlockNo -> Encoding

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

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

ToCBOR EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: EpochNo -> Encoding

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

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

ToCBOR EpochSize 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: EpochSize -> Encoding

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

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

ToCBOR SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: SlotNo -> Encoding

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

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

ToCBOR RelativeTime 
Instance details

Defined in Cardano.Slotting.Time

Methods

toCBOR :: RelativeTime -> Encoding

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

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

ToCBOR SlotLength 
Instance details

Defined in Cardano.Slotting.Time

Methods

toCBOR :: SlotLength -> Encoding

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

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

ToCBOR SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

toCBOR :: SystemStart -> Encoding

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

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

ToCBOR Encoding 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Encoding -> Encoding

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

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

ToCBOR Term 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Term -> Encoding

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

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

ToCBOR InputVRF 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.VRF

Methods

toCBOR :: InputVRF -> Encoding

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

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

ToCBOR Text 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Text -> Encoding

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

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

ToCBOR UTCTime 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: UTCTime -> Encoding

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

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

ToCBOR Integer 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Integer -> Encoding

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

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

ToCBOR Natural 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Natural -> Encoding

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

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

ToCBOR () 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: () -> Encoding

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

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

ToCBOR Bool 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Bool -> Encoding

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

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

ToCBOR Double 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Double -> Encoding

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

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

ToCBOR Float 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Float -> Encoding

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

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

ToCBOR Int 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Int -> Encoding

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

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

ToCBOR Word 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Word -> Encoding

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

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

ToCBOR a => ToCBOR (NonEmpty a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: NonEmpty a -> Encoding

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

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

ToCBOR a => ToCBOR (Ratio a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Ratio a -> Encoding

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

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

IsShelleyBasedEra era => ToCBOR (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

Methods

toCBOR :: Certificate era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Certificate era) -> Size

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

IsShelleyBasedEra era => ToCBOR (Proposal era) 
Instance details

Defined in Cardano.Api.Governance.Actions.ProposalProcedure

Methods

toCBOR :: Proposal era -> Encoding

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

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

IsShelleyBasedEra era => ToCBOR (GovernanceActionId era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

Methods

toCBOR :: GovernanceActionId era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (GovernanceActionId era) -> Size

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

IsShelleyBasedEra era => ToCBOR (Voter era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

Methods

toCBOR :: Voter era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Voter era) -> Size

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

IsShelleyBasedEra era => ToCBOR (VotingProcedure era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

Methods

toCBOR :: VotingProcedure era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VotingProcedure era) -> Size

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

IsShelleyBasedEra era => ToCBOR (VotingProcedures era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

Methods

toCBOR :: VotingProcedures era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VotingProcedures era) -> Size

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

ToCBOR (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: Hash ByronKey -> Encoding

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

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

ToCBOR (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: Hash ByronKeyLegacy -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash ByronKeyLegacy) -> Size

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

ToCBOR (Hash KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

toCBOR :: Hash KesKey -> Encoding

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

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

ToCBOR (Hash VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

toCBOR :: Hash VrfKey -> Encoding

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

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

ToCBOR (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash CommitteeColdExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeColdExtendedKey) -> Size

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

ToCBOR (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash CommitteeColdKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeColdKey) -> Size

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

ToCBOR (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash CommitteeHotExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeHotExtendedKey) -> Size

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

ToCBOR (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash CommitteeHotKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeHotKey) -> Size

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

ToCBOR (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash DRepExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash DRepExtendedKey) -> Size

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

ToCBOR (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash DRepKey -> Encoding

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

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

ToCBOR (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisDelegateExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisDelegateExtendedKey) -> Size

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

ToCBOR (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisDelegateKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisDelegateKey) -> Size

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

ToCBOR (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisExtendedKey) -> Size

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

ToCBOR (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisKey) -> Size

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

ToCBOR (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisUTxOKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisUTxOKey) -> Size

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

ToCBOR (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash PaymentExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash PaymentExtendedKey) -> Size

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

ToCBOR (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash PaymentKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash PaymentKey) -> Size

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

ToCBOR (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash StakeExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash StakeExtendedKey) -> Size

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

ToCBOR (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash StakeKey -> Encoding

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

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

ToCBOR (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash StakePoolKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash StakePoolKey) -> Size

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

ToCBOR (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: SigningKey ByronKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey ByronKey) -> Size

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

ToCBOR (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: SigningKey ByronKeyLegacy -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey ByronKeyLegacy) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey ByronKeyLegacy] -> Size

ToCBOR (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

toCBOR :: SigningKey KesKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey KesKey) -> Size

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

ToCBOR (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

toCBOR :: SigningKey VrfKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey VrfKey) -> Size

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

ToCBOR (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey CommitteeColdExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdExtendedKey] -> Size

ToCBOR (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey CommitteeColdKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdKey] -> Size

ToCBOR (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey CommitteeHotExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotExtendedKey] -> Size

ToCBOR (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey CommitteeHotKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotKey] -> Size

ToCBOR (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey DRepExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey DRepExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey DRepExtendedKey] -> Size

ToCBOR (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey DRepKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey DRepKey) -> Size

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

ToCBOR (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisDelegateExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateExtendedKey] -> Size

ToCBOR (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisDelegateKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateKey] -> Size

ToCBOR (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisExtendedKey] -> Size

ToCBOR (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisKey] -> Size

ToCBOR (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisUTxOKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisUTxOKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisUTxOKey] -> Size

ToCBOR (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey PaymentExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentExtendedKey] -> Size

ToCBOR (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey PaymentKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentKey] -> Size

ToCBOR (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey StakeExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakeExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakeExtendedKey] -> Size

ToCBOR (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey StakeKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakeKey) -> Size

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

ToCBOR (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey StakePoolKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakePoolKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakePoolKey] -> Size

ToCBOR (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: VerificationKey ByronKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey ByronKey) -> Size

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

ToCBOR (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: VerificationKey ByronKeyLegacy -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey ByronKeyLegacy) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey ByronKeyLegacy] -> Size

ToCBOR (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

toCBOR :: VerificationKey KesKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey KesKey) -> Size

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

ToCBOR (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

Methods

toCBOR :: VerificationKey VrfKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey VrfKey) -> Size

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

ToCBOR (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey CommitteeColdKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeColdKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeColdKey] -> Size

ToCBOR (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey CommitteeHotKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeHotKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeHotKey] -> Size

ToCBOR (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey DRepExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey DRepExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey DRepExtendedKey] -> Size

ToCBOR (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey DRepKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey DRepKey) -> Size

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

ToCBOR (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey GenesisDelegateKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisDelegateKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisDelegateKey] -> Size

ToCBOR (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey GenesisExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisExtendedKey] -> Size

ToCBOR (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey GenesisKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisKey] -> Size

ToCBOR (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey GenesisUTxOKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisUTxOKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisUTxOKey] -> Size

ToCBOR (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey PaymentExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentExtendedKey] -> Size

ToCBOR (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey PaymentKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentKey] -> Size

ToCBOR (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey StakeExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakeExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakeExtendedKey] -> Size

ToCBOR (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey StakeKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakeKey) -> Size

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

ToCBOR (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey StakePoolKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakePoolKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakePoolKey] -> Size

HasTypeProxy lang => ToCBOR (PlutusScript lang) 
Instance details

Defined in Cardano.Api.Script

Methods

toCBOR :: PlutusScript lang -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (PlutusScript lang) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [PlutusScript lang] -> Size

SerialiseAsRawBytes a => ToCBOR (UsingRawBytes a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

toCBOR :: UsingRawBytes a -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (UsingRawBytes a) -> Size

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

Typeable xs => ToCBOR (LengthOf xs) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: LengthOf xs -> Encoding

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

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

ToCBOR (SigDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Methods

toCBOR :: SigDSIGN Ed25519DSIGN -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigDSIGN Ed25519DSIGN) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigDSIGN Ed25519DSIGN] -> Size

ToCBOR (SignKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Methods

toCBOR :: SignKeyDSIGN Ed25519DSIGN -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SignKeyDSIGN Ed25519DSIGN) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SignKeyDSIGN Ed25519DSIGN] -> Size

ToCBOR (VerKeyDSIGN Ed25519DSIGN) 
Instance details

Defined in Cardano.Crypto.DSIGN.Ed25519

Methods

toCBOR :: VerKeyDSIGN Ed25519DSIGN -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerKeyDSIGN Ed25519DSIGN) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKeyDSIGN Ed25519DSIGN] -> Size

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

Defined in Cardano.Crypto.KES.Single

Methods

toCBOR :: SigKES (SingleKES d) -> Encoding

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

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

(KESAlgorithm d, HashAlgorithm h) => ToCBOR (SigKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

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

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

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

DSIGNAlgorithm d => ToCBOR (SignKeyKES (SingleKES d)) 
Instance details

Defined in Cardano.Crypto.KES.Single

Methods

toCBOR :: SignKeyKES (SingleKES d) -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SignKeyKES (SingleKES d)) -> Size

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

(KESAlgorithm d, HashAlgorithm h) => ToCBOR (SignKeyKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

toCBOR :: SignKeyKES (SumKES h d) -> Encoding

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

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

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

Defined in Cardano.Crypto.KES.Single

Methods

toCBOR :: VerKeyKES (SingleKES d) -> Encoding

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

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

(KESAlgorithm d, HashAlgorithm h) => ToCBOR (VerKeyKES (SumKES h d)) 
Instance details

Defined in Cardano.Crypto.KES.Sum

Methods

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

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

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

ToCBOR (CertVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

toCBOR :: CertVRF PraosVRF -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (CertVRF PraosVRF) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [CertVRF PraosVRF] -> Size

Typeable v => ToCBOR (OutputVRF v) 
Instance details

Defined in Cardano.Crypto.VRF.Class

Methods

toCBOR :: OutputVRF v -> Encoding

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

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

ToCBOR (SignKeyVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

toCBOR :: SignKeyVRF PraosVRF -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SignKeyVRF PraosVRF) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SignKeyVRF PraosVRF] -> Size

ToCBOR (VerKeyVRF PraosVRF) 
Instance details

Defined in Cardano.Crypto.VRF.Praos

Methods

toCBOR :: VerKeyVRF PraosVRF -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerKeyVRF PraosVRF) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerKeyVRF PraosVRF] -> Size

Typeable era => ToCBOR (Timelock era) 
Instance details

Defined in Cardano.Ledger.Allegra.Scripts

Methods

toCBOR :: Timelock era -> Encoding

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

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

Typeable era => ToCBOR (AllegraTxAuxData era) 
Instance details

Defined in Cardano.Ledger.Allegra.TxAuxData

Methods

toCBOR :: AllegraTxAuxData era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AllegraTxAuxData era) -> Size

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

Typeable e => ToCBOR (AllegraTxBody e) 
Instance details

Defined in Cardano.Ledger.Allegra.TxBody

Methods

toCBOR :: AllegraTxBody e -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AllegraTxBody e) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AllegraTxBody e] -> Size

AlonzoEraScript era => ToCBOR (AlonzoScript era) 
Instance details

Defined in Cardano.Ledger.Alonzo.Scripts

Methods

toCBOR :: AlonzoScript era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoScript era) -> Size

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

(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

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

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

Typeable era => ToCBOR (AlonzoTxAuxData era) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxAuxData

Methods

toCBOR :: AlonzoTxAuxData era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoTxAuxData era) -> Size

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

Typeable era => ToCBOR (AlonzoTxBody era) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxBody

Methods

toCBOR :: AlonzoTxBody era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoTxBody era) -> Size

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

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

Defined in Cardano.Ledger.Alonzo.TxOut

Methods

toCBOR :: AlonzoTxOut era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoTxOut era) -> Size

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

Typeable era => ToCBOR (AlonzoTxWits era) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxWits

Methods

toCBOR :: AlonzoTxWits era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoTxWits era) -> Size

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

Typeable era => ToCBOR (Redeemers era) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxWits

Methods

toCBOR :: Redeemers era -> Encoding

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

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

Typeable era => ToCBOR (TxDats era) 
Instance details

Defined in Cardano.Ledger.Alonzo.TxWits

Methods

toCBOR :: TxDats era -> Encoding

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

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

Typeable era => ToCBOR (BabbageTxBody era) 
Instance details

Defined in Cardano.Ledger.Babbage.TxBody

Methods

toCBOR :: BabbageTxBody era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (BabbageTxBody era) -> Size

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

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

Defined in Cardano.Ledger.Babbage.TxOut

Methods

toCBOR :: BabbageTxOut era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (BabbageTxOut era) -> Size

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

ToCBOR (Attributes AddrAttributes) 
Instance details

Defined in Cardano.Chain.Common.AddrAttributes

Methods

toCBOR :: Attributes AddrAttributes -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Attributes AddrAttributes) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Attributes AddrAttributes] -> Size

EncCBOR n => ToCBOR (TooLarge n) 
Instance details

Defined in Cardano.Chain.Update.Validation.Registration

Methods

toCBOR :: TooLarge n -> Encoding

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

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

EraPParams era => ToCBOR (ConwayGovState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toCBOR :: ConwayGovState era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayGovState era) -> Size

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

EraPParams era => ToCBOR (EnactState era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toCBOR :: EnactState era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (EnactState era) -> Size

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

EraPParams era => ToCBOR (PulsingSnapshot era) 
Instance details

Defined in Cardano.Ledger.Conway.Governance

Methods

toCBOR :: PulsingSnapshot era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (PulsingSnapshot era) -> Size

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

EraPParams era => ToCBOR (ConwayGovPredFailure era) 
Instance details

Defined in Cardano.Ledger.Conway.Rules.Gov

Methods

toCBOR :: ConwayGovPredFailure era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayGovPredFailure era) -> Size

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

Typeable era => ToCBOR (ConwayTxBody era) 
Instance details

Defined in Cardano.Ledger.Conway.TxBody

Methods

toCBOR :: ConwayTxBody era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayTxBody era) -> Size

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

(Era era, Val (Value era)) => ToCBOR (ConwayTxCert era) 
Instance details

Defined in Cardano.Ledger.Conway.TxCert

Methods

toCBOR :: ConwayTxCert era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayTxCert era) -> Size

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

Era era => ToCBOR (CommitteeState era) 
Instance details

Defined in Cardano.Ledger.CertState

Methods

toCBOR :: CommitteeState era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (CommitteeState era) -> Size

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

ToCBOR (CompactForm Coin) 
Instance details

Defined in Cardano.Ledger.Coin

Methods

toCBOR :: CompactForm Coin -> Encoding

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

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

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

Defined in Cardano.Ledger.Core.PParams

Methods

toCBOR :: PParams era -> Encoding

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

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

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

Defined in Cardano.Ledger.Core.PParams

Methods

toCBOR :: PParamsUpdate era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (PParamsUpdate era) -> Size

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

Crypto c => ToCBOR (GenesisCredential c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

toCBOR :: GenesisCredential c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (GenesisCredential c) -> Size

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

Crypto c => ToCBOR (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

toCBOR :: ScriptHash c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ScriptHash c) -> Size

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

Crypto c => ToCBOR (BootstrapWitness c) 
Instance details

Defined in Cardano.Ledger.Keys.Bootstrap

Methods

toCBOR :: BootstrapWitness c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (BootstrapWitness c) -> Size

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

Typeable era => ToCBOR (Data era) 
Instance details

Defined in Cardano.Ledger.Plutus.Data

Methods

toCBOR :: Data era -> Encoding

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

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

PlutusLanguage l => ToCBOR (SLanguage l) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

Methods

toCBOR :: SLanguage l -> Encoding

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

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

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

Defined in Cardano.Ledger.UTxO

Methods

toCBOR :: UTxO era -> Encoding

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

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

Typeable era => ToCBOR (MaryTxBody era) 
Instance details

Defined in Cardano.Ledger.Mary.TxBody

Methods

toCBOR :: MaryTxBody era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (MaryTxBody era) -> Size

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

(Era era, EncCBOR (PredicateFailure (EraRule "LEDGER" era))) => ToCBOR (ApplyTxError era) 
Instance details

Defined in Cardano.Ledger.Shelley.API.Mempool

Methods

toCBOR :: ApplyTxError era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ApplyTxError era) -> Size

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

Crypto c => ToCBOR (ShelleyGenesis c) 
Instance details

Defined in Cardano.Ledger.Shelley.Genesis

Methods

toCBOR :: ShelleyGenesis c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyGenesis c) -> Size

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

Era era => ToCBOR (Constitution era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

toCBOR :: Constitution era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Constitution era) -> Size

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

(Era era, EncCBOR (PParamsUpdate era), EncCBOR (PParams era)) => ToCBOR (ShelleyGovState era) 
Instance details

Defined in Cardano.Ledger.Shelley.Governance

Methods

toCBOR :: ShelleyGovState era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyGovState era) -> Size

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

(EraTxOut era, EraGov era) => ToCBOR (EpochState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

toCBOR :: EpochState era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (EpochState era) -> Size

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

(EraTxOut era, EraGov era) => ToCBOR (LedgerState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

toCBOR :: LedgerState era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (LedgerState era) -> Size

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

(EraTxOut era, EraGov era, EncCBOR (StashedAVVMAddresses era)) => ToCBOR (NewEpochState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

toCBOR :: NewEpochState era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (NewEpochState era) -> Size

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

(EraTxOut era, EraGov era) => ToCBOR (UTxOState era) 
Instance details

Defined in Cardano.Ledger.Shelley.LedgerState.Types

Methods

toCBOR :: UTxOState era -> Encoding

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

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

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

Defined in Cardano.Ledger.Shelley.PParams

Methods

toCBOR :: ProposedPPUpdates era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ProposedPPUpdates era) -> Size

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

Typeable era => ToCBOR (MultiSig era) 
Instance details

Defined in Cardano.Ledger.Shelley.Scripts

Methods

toCBOR :: MultiSig era -> Encoding

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

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

Typeable era => ToCBOR (ShelleyTx era) 
Instance details

Defined in Cardano.Ledger.Shelley.Tx

Methods

toCBOR :: ShelleyTx era -> Encoding

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

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

Typeable era => ToCBOR (ShelleyTxAuxData era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxAuxData

Methods

toCBOR :: ShelleyTxAuxData era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxAuxData era) -> Size

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

Typeable era => ToCBOR (ShelleyTxBody era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Methods

toCBOR :: ShelleyTxBody era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxBody era) -> Size

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

Era era => ToCBOR (ShelleyTxCert era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toCBOR :: ShelleyTxCert era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxCert era) -> Size

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

(Era era, EncCBOR (CompactForm (Value era))) => ToCBOR (ShelleyTxOut era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxOut

Methods

toCBOR :: ShelleyTxOut era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxOut era) -> Size

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

Era era => ToCBOR (ShelleyTxWits era) 
Instance details

Defined in Cardano.Ledger.Shelley.TxWits

Methods

toCBOR :: ShelleyTxWits era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyTxWits era) -> Size

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

Crypto c => ToCBOR (ChainDepState c) 
Instance details

Defined in Cardano.Protocol.TPraos.API

Methods

toCBOR :: ChainDepState c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ChainDepState c) -> Size

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

Crypto c => ToCBOR (OCert c) 
Instance details

Defined in Cardano.Protocol.TPraos.OCert

Methods

toCBOR :: OCert c -> Encoding

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

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

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

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: WithOrigin t -> Encoding

encodedSizeExpr :: (forall t0. ToCBOR t0 => Proxy t0 -> Size) -> Proxy (WithOrigin t) -> Size

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

ToCBOR a => ToCBOR (StrictMaybe a) 
Instance details

Defined in Data.Maybe.Strict

Methods

toCBOR :: StrictMaybe a -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (StrictMaybe a) -> Size

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

ToCBOR a => ToCBOR (StrictSeq a) 
Instance details

Defined in Data.Sequence.Strict

Methods

toCBOR :: StrictSeq a -> Encoding

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

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

ToCBOR a => ToCBOR (Seq a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Seq a -> Encoding

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

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

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

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Set a -> Encoding

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

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

Crypto c => ToCBOR (CompactGenesis c) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

toCBOR :: CompactGenesis c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (CompactGenesis c) -> Size

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

Crypto c => ToCBOR (NonMyopicMemberRewards c) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBOR :: NonMyopicMemberRewards c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (NonMyopicMemberRewards c) -> Size

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

Crypto crypto => ToCBOR (StakeSnapshot crypto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBOR :: StakeSnapshot crypto -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (StakeSnapshot crypto) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StakeSnapshot crypto] -> Size

Crypto crypto => ToCBOR (StakeSnapshots crypto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

toCBOR :: StakeSnapshots crypto -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (StakeSnapshots crypto) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [StakeSnapshots crypto] -> Size

Crypto c => ToCBOR (LegacyPParams (AllegraEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query.PParamsLegacyEncoder

Methods

toCBOR :: LegacyPParams (AllegraEra c) -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (LegacyPParams (AllegraEra c)) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [LegacyPParams (AllegraEra c)] -> Size

Crypto c => ToCBOR (LegacyPParams (AlonzoEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query.PParamsLegacyEncoder

Methods

toCBOR :: LegacyPParams (AlonzoEra c) -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (LegacyPParams (AlonzoEra c)) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [LegacyPParams (AlonzoEra c)] -> Size

Crypto c => ToCBOR (LegacyPParams (BabbageEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query.PParamsLegacyEncoder

Methods

toCBOR :: LegacyPParams (BabbageEra c) -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (LegacyPParams (BabbageEra c)) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [LegacyPParams (BabbageEra c)] -> Size

Crypto c => ToCBOR (LegacyPParams (ConwayEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query.PParamsLegacyEncoder

Methods

toCBOR :: LegacyPParams (ConwayEra c) -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (LegacyPParams (ConwayEra c)) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [LegacyPParams (ConwayEra c)] -> Size

Crypto c => ToCBOR (LegacyPParams (MaryEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query.PParamsLegacyEncoder

Methods

toCBOR :: LegacyPParams (MaryEra c) -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (LegacyPParams (MaryEra c)) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [LegacyPParams (MaryEra c)] -> Size

Crypto c => ToCBOR (LegacyPParams (ShelleyEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query.PParamsLegacyEncoder

Methods

toCBOR :: LegacyPParams (ShelleyEra c) -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (LegacyPParams (ShelleyEra c)) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [LegacyPParams (ShelleyEra c)] -> Size

Crypto crypto => ToCBOR (ShelleyHash crypto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

toCBOR :: ShelleyHash crypto -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyHash crypto) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyHash crypto] -> Size

PraosCrypto c => ToCBOR (PraosState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

Methods

toCBOR :: PraosState c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (PraosState c) -> Size

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

Crypto c => ToCBOR (Header c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos.Header

Methods

toCBOR :: Header c -> Encoding

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

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

PraosCrypto c => ToCBOR (TPraosState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

Methods

toCBOR :: TPraosState c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (TPraosState c) -> Size

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

ToCBOR a => ToCBOR (Vector a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Vector a -> Encoding

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

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

ToCBOR a => ToCBOR (Maybe a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Maybe a -> Encoding

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

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

ToCBOR a => ToCBOR [a] 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: [a] -> Encoding

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

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

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

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Either a b -> Encoding

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

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

Typeable a => ToCBOR (Fixed a) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Fixed a -> Encoding

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

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

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

Defined in Cardano.Crypto.Hash.Class

Methods

toCBOR :: Hash h a -> Encoding

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

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

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

Defined in Cardano.Crypto.VRF.Class

Methods

toCBOR :: CertifiedVRF v a -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (CertifiedVRF v a) -> Size

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

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

Defined in Cardano.Ledger.Alonzo.PParams

Methods

toCBOR :: AlonzoPParams Identity era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoPParams Identity era) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoPParams Identity era] -> Size

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

Defined in Cardano.Ledger.Alonzo.PParams

Methods

toCBOR :: AlonzoPParams StrictMaybe era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (AlonzoPParams StrictMaybe era) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [AlonzoPParams StrictMaybe era] -> Size

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

Defined in Cardano.Ledger.Babbage.PParams

Methods

toCBOR :: BabbagePParams Identity era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (BabbagePParams Identity era) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BabbagePParams Identity era] -> Size

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

Defined in Cardano.Ledger.Babbage.PParams

Methods

toCBOR :: BabbagePParams StrictMaybe era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (BabbagePParams StrictMaybe era) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [BabbagePParams StrictMaybe era] -> Size

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

Defined in Cardano.Ledger.Conway.PParams

Methods

toCBOR :: ConwayPParams Identity era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayPParams Identity era) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayPParams Identity era] -> Size

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

Defined in Cardano.Ledger.Conway.PParams

Methods

toCBOR :: ConwayPParams StrictMaybe era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ConwayPParams StrictMaybe era) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ConwayPParams StrictMaybe era] -> Size

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

Defined in Cardano.Ledger.Block

Methods

toCBOR :: Block h era -> Encoding

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

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

(Typeable kr, Crypto c) => ToCBOR (Credential kr c) 
Instance details

Defined in Cardano.Ledger.Credential

Methods

toCBOR :: Credential kr c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Credential kr c) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [Credential kr c] -> Size

(Crypto c, Typeable disc) => ToCBOR (KeyHash disc c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

toCBOR :: KeyHash disc c -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (KeyHash disc c) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [KeyHash disc c] -> Size

(Crypto c, Typeable kd) => ToCBOR (VKey kd c) 
Instance details

Defined in Cardano.Ledger.Keys.Internal

Methods

toCBOR :: VKey kd c -> Encoding

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

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

(Typeable kr, Crypto c) => ToCBOR (WitVKey kr c) 
Instance details

Defined in Cardano.Ledger.Keys.WitVKey

Methods

toCBOR :: WitVKey kr c -> Encoding

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

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

(Typeable t, Typeable era) => ToCBOR (MemoBytes t era) 
Instance details

Defined in Cardano.Ledger.MemoBytes

Methods

toCBOR :: MemoBytes t era -> Encoding

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

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

(Typeable index, Crypto c) => ToCBOR (SafeHash c index) 
Instance details

Defined in Cardano.Ledger.SafeHash

Methods

toCBOR :: SafeHash c index -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SafeHash c index) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SafeHash c index] -> Size

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

Defined in Cardano.Ledger.Shelley.PParams

Methods

toCBOR :: ShelleyPParams Identity era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyPParams Identity era) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyPParams Identity era] -> Size

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

Defined in Cardano.Ledger.Shelley.PParams

Methods

toCBOR :: ShelleyPParams StrictMaybe era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (ShelleyPParams StrictMaybe era) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [ShelleyPParams StrictMaybe era] -> Size

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

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Map k v -> Encoding

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

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

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

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: (a, b) -> Encoding

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

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

ToCBOR (Tokens -> Tokens) 
Instance details

Defined in Cardano.Binary.ToCBOR

Methods

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

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

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

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

Defined in Cardano.Binary.ToCBOR

Methods

toCBOR :: Tagged s a -> Encoding

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

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

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

Defined in Cardano.Binary.ToCBOR

Methods

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

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

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

(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

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

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

(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

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

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

(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

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

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

(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

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

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

(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

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

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

data PaymentKey #

Instances

Instances details
HasTypeProxy PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType PaymentKey #

Key PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastSigningKeyRole GenesisUTxOKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole ByronKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Byron

CastVerificationKeyRole CommitteeColdKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole CommitteeHotKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole GenesisKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole GenesisUTxOKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole PaymentExtendedKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromJSON (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

parseJSON :: Value -> Parser (Hash PaymentKey) #

parseJSONList :: Value -> Parser [Hash PaymentKey] #

omittedField :: Maybe (Hash PaymentKey) #

FromJSON (VerificationKey PaymentKey) Source # 
Instance details

Defined in Hydra.Cardano.Api.VerificationKey

ToJSON (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toJSON :: Hash PaymentKey -> Value #

toEncoding :: Hash PaymentKey -> Encoding #

toJSONList :: [Hash PaymentKey] -> Value #

toEncodingList :: [Hash PaymentKey] -> Encoding #

omitField :: Hash PaymentKey -> Bool #

ToJSON (VerificationKey PaymentKey) Source # 
Instance details

Defined in Hydra.Cardano.Api.VerificationKey

ToJSONKey (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toJSONKey :: ToJSONKeyFunction (Hash PaymentKey)

toJSONKeyList :: ToJSONKeyFunction [Hash PaymentKey]

IsString (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash PaymentKey)

label :: Proxy (Hash PaymentKey) -> Text

FromCBOR (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash PaymentKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash PaymentKey) -> Size

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

ToCBOR (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey PaymentKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentKey] -> Size

ToCBOR (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey PaymentKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentKey] -> Size

Eq (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data BabbageEra #

Instances

Instances details
IsShelleyBasedEra BabbageEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

IsCardanoEra BabbageEra 
Instance details

Defined in Cardano.Api.Eras.Core

HasTypeProxy BabbageEra 
Instance details

Defined in Cardano.Api.Eras.Core

Associated Types

data AsType BabbageEra #

IsAllegraEraOnwards BabbageEra 
Instance details

Defined in Cardano.Api.Class.IsAllegraEraOnwards

IsAlonzoEraOnwards BabbageEra 
Instance details

Defined in Cardano.Api.Class.IsAlonzoEraOnwards

IsBabbageEraOnwards BabbageEra 
Instance details

Defined in Cardano.Api.Class.IsBabbageEraOnwards

IsMaryEraOnwards BabbageEra 
Instance details

Defined in Cardano.Api.Class.IsMaryEraOnwards

HasScriptLanguageInEra PlutusScriptV1 BabbageEra 
Instance details

Defined in Cardano.Api.Class.HasScriptLanguageInEra

HasScriptLanguageInEra PlutusScriptV2 BabbageEra 
Instance details

Defined in Cardano.Api.Class.HasScriptLanguageInEra

ToAlonzoScript PlutusScriptV1 BabbageEra 
Instance details

Defined in Cardano.Api.Class.ToAlonzoScript

ToAlonzoScript PlutusScriptV2 BabbageEra 
Instance details

Defined in Cardano.Api.Class.ToAlonzoScript

Arbitrary (TxValidityLowerBound Era) Source # 
Instance details

Defined in Hydra.Cardano.Api.ValidityInterval

Arbitrary (TxValidityUpperBound Era) Source # 
Instance details

Defined in Hydra.Cardano.Api.ValidityInterval

data AsType BabbageEra 
Instance details

Defined in Cardano.Api.Eras.Core

data AddressAny #

Instances

Instances details
Show AddressAny 
Instance details

Defined in Cardano.Api.Address

SerialiseAddress AddressAny 
Instance details

Defined in Cardano.Api.Address

HasTypeProxy AddressAny 
Instance details

Defined in Cardano.Api.Address

Associated Types

data AsType AddressAny #

SerialiseAsRawBytes AddressAny 
Instance details

Defined in Cardano.Api.Address

Eq AddressAny 
Instance details

Defined in Cardano.Api.Address

Ord AddressAny 
Instance details

Defined in Cardano.Api.Address

data AsType AddressAny 
Instance details

Defined in Cardano.Api.Address

data ByronAddr #

Instances

Instances details
HasTypeProxy ByronAddr 
Instance details

Defined in Cardano.Api.Address

Associated Types

data AsType ByronAddr #

Arbitrary (Address ByronAddr) Source # 
Instance details

Defined in Hydra.Cardano.Api.Address

FromJSON (Address ByronAddr) 
Instance details

Defined in Cardano.Api.Address

Methods

parseJSON :: Value -> Parser (Address ByronAddr) #

parseJSONList :: Value -> Parser [Address ByronAddr] #

omittedField :: Maybe (Address ByronAddr) #

ToJSON (Address ByronAddr) 
Instance details

Defined in Cardano.Api.Address

SerialiseAddress (Address ByronAddr) 
Instance details

Defined in Cardano.Api.Address

SerialiseAsRawBytes (Address ByronAddr) 
Instance details

Defined in Cardano.Api.Address

data AsType ByronAddr 
Instance details

Defined in Cardano.Api.Address

data ShelleyAddr #

Instances

Instances details
HasTypeProxy ShelleyAddr 
Instance details

Defined in Cardano.Api.Address

Associated Types

data AsType ShelleyAddr #

FromJSON (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

Methods

parseJSON :: Value -> Parser (Address ShelleyAddr) #

parseJSONList :: Value -> Parser [Address ShelleyAddr] #

omittedField :: Maybe (Address ShelleyAddr) #

ToJSON (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

SerialiseAddress (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

SerialiseAsBech32 (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

SerialiseAsRawBytes (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

data AsType ShelleyAddr 
Instance details

Defined in Cardano.Api.Address

data StakeAddress #

Instances

Instances details
FromJSON StakeAddress 
Instance details

Defined in Cardano.Api.Address

Methods

parseJSON :: Value -> Parser StakeAddress #

parseJSONList :: Value -> Parser [StakeAddress] #

omittedField :: Maybe StakeAddress #

ToJSON StakeAddress 
Instance details

Defined in Cardano.Api.Address

Methods

toJSON :: StakeAddress -> Value #

toEncoding :: StakeAddress -> Encoding #

toJSONList :: [StakeAddress] -> Value #

toEncodingList :: [StakeAddress] -> Encoding #

omitField :: StakeAddress -> Bool #

Show StakeAddress 
Instance details

Defined in Cardano.Api.Address

SerialiseAddress StakeAddress 
Instance details

Defined in Cardano.Api.Address

HasTypeProxy StakeAddress 
Instance details

Defined in Cardano.Api.Address

Associated Types

data AsType StakeAddress #

SerialiseAsBech32 StakeAddress 
Instance details

Defined in Cardano.Api.Address

SerialiseAsRawBytes StakeAddress 
Instance details

Defined in Cardano.Api.Address

Eq StakeAddress 
Instance details

Defined in Cardano.Api.Address

Ord StakeAddress 
Instance details

Defined in Cardano.Api.Address

data AsType StakeAddress 
Instance details

Defined in Cardano.Api.Address

newtype AnchorDataHash #

Constructors

AnchorDataHash 

Fields

newtype AnchorUrl #

Constructors

AnchorUrl 

Fields

Instances

Instances details
Show AnchorUrl 
Instance details

Defined in Cardano.Api.Anchor

Eq AnchorUrl 
Instance details

Defined in Cardano.Api.Anchor

data BlockInMode where #

Constructors

BlockInMode :: forall era. CardanoEra era -> Block era -> BlockInMode 

Instances

Instances details
Show BlockInMode 
Instance details

Defined in Cardano.Api.Block

data ChainTip #

Instances

Instances details
ToJSON ChainTip 
Instance details

Defined in Cardano.Api.Block

Methods

toJSON :: ChainTip -> Value #

toEncoding :: ChainTip -> Encoding #

toJSONList :: [ChainTip] -> Value #

toEncodingList :: [ChainTip] -> Encoding #

omitField :: ChainTip -> Bool #

Show ChainTip 
Instance details

Defined in Cardano.Api.Block

Eq ChainTip 
Instance details

Defined in Cardano.Api.Block

data Certificate era where #

Constructors

ShelleyRelatedCertificate :: forall era. ShelleyToBabbageEra era -> ShelleyTxCert (ShelleyLedgerEra era) -> Certificate era 
ConwayCertificate :: forall era. ConwayEraOnwards era -> ConwayTxCert (ShelleyLedgerEra era) -> Certificate era 

Instances

Instances details
Show (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

Typeable era => HasTypeProxy (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

Associated Types

data AsType (Certificate era) #

IsShelleyBasedEra era => SerialiseAsCBOR (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

IsShelleyBasedEra era => HasTextEnvelope (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

IsShelleyBasedEra era => FromCBOR (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

Methods

fromCBOR :: Decoder s (Certificate era)

label :: Proxy (Certificate era) -> Text

IsShelleyBasedEra era => ToCBOR (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

Methods

toCBOR :: Certificate era -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Certificate era) -> Size

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

Eq (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

Methods

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

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

data AsType (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

data CommitteeColdkeyResignationRequirements era where #

Constructors

CommitteeColdkeyResignationRequirements :: forall era. ConwayEraOnwards era -> Credential 'ColdCommitteeRole (EraCrypto (ShelleyLedgerEra era)) -> Maybe (Anchor (EraCrypto (ShelleyLedgerEra era))) -> CommitteeColdkeyResignationRequirements era 

data CommitteeHotKeyAuthorizationRequirements era where #

Constructors

CommitteeHotKeyAuthorizationRequirements :: forall era. ConwayEraOnwards era -> Credential 'ColdCommitteeRole (EraCrypto (ShelleyLedgerEra era)) -> Credential 'HotCommitteeRole (EraCrypto (ShelleyLedgerEra era)) -> CommitteeHotKeyAuthorizationRequirements era 

data DRepRegistrationRequirements era where #

Constructors

DRepRegistrationRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole (EraCrypto (ShelleyLedgerEra era)) -> Coin -> DRepRegistrationRequirements era 

data DRepUnregistrationRequirements era where #

Constructors

DRepUnregistrationRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole (EraCrypto (ShelleyLedgerEra era)) -> Coin -> DRepUnregistrationRequirements era 

data DRepUpdateRequirements era where #

Constructors

DRepUpdateRequirements :: forall era. ConwayEraOnwards era -> Credential 'DRepRole (EraCrypto (ShelleyLedgerEra era)) -> DRepUpdateRequirements era 

data DRepMetadata #

Instances

Instances details
Show DRepMetadata 
Instance details

Defined in Cardano.Api.DRepMetadata

HasTypeProxy DRepMetadata 
Instance details

Defined in Cardano.Api.DRepMetadata

Associated Types

data AsType DRepMetadata #

Eq DRepMetadata 
Instance details

Defined in Cardano.Api.DRepMetadata

Show (Hash DRepMetadata) 
Instance details

Defined in Cardano.Api.DRepMetadata

SerialiseAsRawBytes (Hash DRepMetadata) 
Instance details

Defined in Cardano.Api.DRepMetadata

Eq (Hash DRepMetadata) 
Instance details

Defined in Cardano.Api.DRepMetadata

data AsType DRepMetadata 
Instance details

Defined in Cardano.Api.DRepMetadata

newtype Hash DRepMetadata 
Instance details

Defined in Cardano.Api.DRepMetadata

data InputDecodeError #

Instances

Instances details
Data InputDecodeError 
Instance details

Defined in Cardano.Api.DeserialiseAnyOf

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> InputDecodeError -> c InputDecodeError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c InputDecodeError Source #

toConstr :: InputDecodeError -> Constr Source #

dataTypeOf :: InputDecodeError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c InputDecodeError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c InputDecodeError) Source #

gmapT :: (forall b. Data b => b -> b) -> InputDecodeError -> InputDecodeError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> InputDecodeError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> InputDecodeError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> InputDecodeError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> InputDecodeError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> InputDecodeError -> m InputDecodeError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> InputDecodeError -> m InputDecodeError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> InputDecodeError -> m InputDecodeError Source #

Show InputDecodeError 
Instance details

Defined in Cardano.Api.DeserialiseAnyOf

Error InputDecodeError 
Instance details

Defined in Cardano.Api.DeserialiseAnyOf

Eq InputDecodeError 
Instance details

Defined in Cardano.Api.DeserialiseAnyOf

data ConwayEraOnwards era where #

Instances

Instances details
Eon ConwayEraOnwards 
Instance details

Defined in Cardano.Api.Eon.ConwayEraOnwards

Methods

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

ToCardanoEra ConwayEraOnwards 
Instance details

Defined in Cardano.Api.Eon.ConwayEraOnwards

Show (ConwayEraOnwards era) 
Instance details

Defined in Cardano.Api.Eon.ConwayEraOnwards

Eq (ConwayEraOnwards era) 
Instance details

Defined in Cardano.Api.Eon.ConwayEraOnwards

data AnyShelleyBasedEra where #

Constructors

AnyShelleyBasedEra :: forall era. Typeable era => ShelleyBasedEra era -> AnyShelleyBasedEra 

Instances

Instances details
FromJSON AnyShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

ToJSON AnyShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Bounded AnyShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Enum AnyShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Show AnyShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Eq AnyShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

data InAnyShelleyBasedEra (thing :: Type -> Type) where #

Constructors

InAnyShelleyBasedEra :: forall era (thing :: Type -> Type). Typeable era => ShelleyBasedEra era -> thing era -> InAnyShelleyBasedEra thing 

data ShelleyBasedEra era where #

Instances

Instances details
Eon ShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Methods

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

ToCardanoEra ShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

TestEquality ShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Methods

testEquality :: forall (a :: k) (b :: k). ShelleyBasedEra a -> ShelleyBasedEra b -> Maybe (a :~: b) Source #

ToJSON (ShelleyBasedEra era) 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Methods

toJSON :: ShelleyBasedEra era -> Value #

toEncoding :: ShelleyBasedEra era -> Encoding #

toJSONList :: [ShelleyBasedEra era] -> Value #

toEncodingList :: [ShelleyBasedEra era] -> Encoding #

omitField :: ShelleyBasedEra era -> Bool #

Show (ShelleyBasedEra era) 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

NFData (ShelleyBasedEra era) 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Methods

rnf :: ShelleyBasedEra era -> () Source #

Eq (ShelleyBasedEra era) 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Ord (ShelleyBasedEra era) 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Pretty (ShelleyBasedEra era) 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Methods

pretty :: ShelleyBasedEra era -> Doc ann #

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

data ShelleyEraOnly era where #

Instances

Instances details
Eon ShelleyEraOnly 
Instance details

Defined in Cardano.Api.Eon.ShelleyEraOnly

Methods

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

ToCardanoEra ShelleyEraOnly 
Instance details

Defined in Cardano.Api.Eon.ShelleyEraOnly

Show (ShelleyEraOnly era) 
Instance details

Defined in Cardano.Api.Eon.ShelleyEraOnly

Eq (ShelleyEraOnly era) 
Instance details

Defined in Cardano.Api.Eon.ShelleyEraOnly

data AnyCardanoEra where #

Constructors

AnyCardanoEra :: forall era. Typeable era => CardanoEra era -> AnyCardanoEra 

Instances

Instances details
FromJSON AnyCardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

parseJSON :: Value -> Parser AnyCardanoEra #

parseJSONList :: Value -> Parser [AnyCardanoEra] #

omittedField :: Maybe AnyCardanoEra #

ToJSON AnyCardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

toJSON :: AnyCardanoEra -> Value #

toEncoding :: AnyCardanoEra -> Encoding #

toJSONList :: [AnyCardanoEra] -> Value #

toEncodingList :: [AnyCardanoEra] -> Encoding #

omitField :: AnyCardanoEra -> Bool #

Bounded AnyCardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Enum AnyCardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Show AnyCardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Eq AnyCardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Pretty AnyCardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

pretty :: AnyCardanoEra -> Doc ann #

prettyList :: [AnyCardanoEra] -> Doc ann #

data ByronEra #

Instances

Instances details
IsCardanoEra ByronEra 
Instance details

Defined in Cardano.Api.Eras.Core

HasTypeProxy ByronEra 
Instance details

Defined in Cardano.Api.Eras.Core

Associated Types

data AsType ByronEra #

data AsType ByronEra 
Instance details

Defined in Cardano.Api.Eras.Core

data CardanoEra era where #

Instances

Instances details
Eon CardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

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

ToCardanoEra CardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

toCardanoEra :: CardanoEra era -> CardanoEra era #

TestEquality CardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

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

ToJSON (CardanoEra era) 
Instance details

Defined in Cardano.Api.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) 
Instance details

Defined in Cardano.Api.Eras.Core

Eq (CardanoEra era) 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

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

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

Ord (CardanoEra era) 
Instance details

Defined in Cardano.Api.Eras.Core

Pretty (CardanoEra era) 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

pretty :: CardanoEra era -> Doc ann #

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

data ConwayEra #

Instances

Instances details
IsShelleyBasedEra ConwayEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

IsCardanoEra ConwayEra 
Instance details

Defined in Cardano.Api.Eras.Core

HasTypeProxy ConwayEra 
Instance details

Defined in Cardano.Api.Eras.Core

Associated Types

data AsType ConwayEra #

IsAllegraEraOnwards ConwayEra 
Instance details

Defined in Cardano.Api.Class.IsAllegraEraOnwards

IsAlonzoEraOnwards ConwayEra 
Instance details

Defined in Cardano.Api.Class.IsAlonzoEraOnwards

IsBabbageEraOnwards ConwayEra 
Instance details

Defined in Cardano.Api.Class.IsBabbageEraOnwards

IsMaryEraOnwards ConwayEra 
Instance details

Defined in Cardano.Api.Class.IsMaryEraOnwards

HasScriptLanguageInEra PlutusScriptV1 ConwayEra 
Instance details

Defined in Cardano.Api.Class.HasScriptLanguageInEra

HasScriptLanguageInEra PlutusScriptV2 ConwayEra 
Instance details

Defined in Cardano.Api.Class.HasScriptLanguageInEra

HasScriptLanguageInEra PlutusScriptV3 ConwayEra 
Instance details

Defined in Cardano.Api.Class.HasScriptLanguageInEra

ToAlonzoScript PlutusScriptV1 ConwayEra 
Instance details

Defined in Cardano.Api.Class.ToAlonzoScript

ToAlonzoScript PlutusScriptV2 ConwayEra 
Instance details

Defined in Cardano.Api.Class.ToAlonzoScript

ToAlonzoScript PlutusScriptV3 ConwayEra 
Instance details

Defined in Cardano.Api.Class.ToAlonzoScript

data AsType ConwayEra 
Instance details

Defined in Cardano.Api.Eras.Core

data ShelleyEra #

Instances

Instances details
IsShelleyBasedEra ShelleyEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

IsCardanoEra ShelleyEra 
Instance details

Defined in Cardano.Api.Eras.Core

HasTypeProxy ShelleyEra 
Instance details

Defined in Cardano.Api.Eras.Core

Associated Types

data AsType ShelleyEra #

data AsType ShelleyEra 
Instance details

Defined in Cardano.Api.Eras.Core

class Eon (eon :: Type -> Type) where #

Methods

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

Instances

Instances details
Eon AllegraEraOnwards 
Instance details

Defined in Cardano.Api.Eon.AllegraEraOnwards

Methods

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

Eon AlonzoEraOnwards 
Instance details

Defined in Cardano.Api.Eon.AlonzoEraOnwards

Methods

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

Eon BabbageEraOnwards 
Instance details

Defined in Cardano.Api.Eon.BabbageEraOnwards

Methods

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

Eon ByronToAlonzoEra 
Instance details

Defined in Cardano.Api.Eon.ByronToAlonzoEra

Methods

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

Eon ConwayEraOnwards 
Instance details

Defined in Cardano.Api.Eon.ConwayEraOnwards

Methods

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

Eon MaryEraOnwards 
Instance details

Defined in Cardano.Api.Eon.MaryEraOnwards

Methods

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

Eon ShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

Methods

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

Eon ShelleyEraOnly 
Instance details

Defined in Cardano.Api.Eon.ShelleyEraOnly

Methods

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

Eon ShelleyToAllegraEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyToAllegraEra

Methods

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

Eon ShelleyToAlonzoEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyToAlonzoEra

Methods

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

Eon ShelleyToBabbageEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyToBabbageEra

Methods

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

Eon ShelleyToMaryEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyToMaryEra

Methods

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

Eon CardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

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

data EraInEon (eon :: Type -> Type) where #

Constructors

EraInEon :: forall era (eon :: Type -> Type). (Typeable era, Typeable (eon era), Eon eon) => eon era -> EraInEon eon 

Instances

Instances details
Show (EraInEon eon) 
Instance details

Defined in Cardano.Api.Eras.Core

TestEquality eon => Eq (EraInEon eon) 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

(==) :: EraInEon eon -> EraInEon eon -> Bool Source #

(/=) :: EraInEon eon -> EraInEon eon -> Bool Source #

data InAnyCardanoEra (thing :: Type -> Type) where #

Constructors

InAnyCardanoEra :: forall era (thing :: Type -> Type). Typeable era => CardanoEra era -> thing era -> InAnyCardanoEra thing 

class HasTypeProxy era => IsCardanoEra era where #

Methods

cardanoEra :: CardanoEra era #

Instances

Instances details
IsCardanoEra AllegraEra 
Instance details

Defined in Cardano.Api.Eras.Core

IsCardanoEra AlonzoEra 
Instance details

Defined in Cardano.Api.Eras.Core

IsCardanoEra BabbageEra 
Instance details

Defined in Cardano.Api.Eras.Core

IsCardanoEra ByronEra 
Instance details

Defined in Cardano.Api.Eras.Core

IsCardanoEra ConwayEra 
Instance details

Defined in Cardano.Api.Eras.Core

IsCardanoEra MaryEra 
Instance details

Defined in Cardano.Api.Eras.Core

IsCardanoEra ShelleyEra 
Instance details

Defined in Cardano.Api.Eras.Core

class ToCardanoEra (eon :: Type -> Type) where #

Methods

toCardanoEra :: eon era -> CardanoEra era #

Instances

Instances details
ToCardanoEra AllegraEraOnwards 
Instance details

Defined in Cardano.Api.Eon.AllegraEraOnwards

ToCardanoEra AlonzoEraOnwards 
Instance details

Defined in Cardano.Api.Eon.AlonzoEraOnwards

ToCardanoEra BabbageEraOnwards 
Instance details

Defined in Cardano.Api.Eon.BabbageEraOnwards

ToCardanoEra ByronToAlonzoEra 
Instance details

Defined in Cardano.Api.Eon.ByronToAlonzoEra

ToCardanoEra ConwayEraOnwards 
Instance details

Defined in Cardano.Api.Eon.ConwayEraOnwards

ToCardanoEra MaryEraOnwards 
Instance details

Defined in Cardano.Api.Eon.MaryEraOnwards

ToCardanoEra ShelleyBasedEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyBasedEra

ToCardanoEra ShelleyEraOnly 
Instance details

Defined in Cardano.Api.Eon.ShelleyEraOnly

ToCardanoEra ShelleyToAllegraEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyToAllegraEra

ToCardanoEra ShelleyToAlonzoEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyToAlonzoEra

ToCardanoEra ShelleyToBabbageEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyToBabbageEra

ToCardanoEra ShelleyToMaryEra 
Instance details

Defined in Cardano.Api.Eon.ShelleyToMaryEra

ToCardanoEra CardanoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Methods

toCardanoEra :: CardanoEra era -> CardanoEra era #

data FileError e #

Instances

Instances details
Functor FileError 
Instance details

Defined in Cardano.Api.Error

Methods

fmap :: (a -> b) -> FileError a -> FileError b Source #

(<$) :: a -> FileError b -> FileError a Source #

Show e => Show (FileError e) 
Instance details

Defined in Cardano.Api.Error

Error e => Error (FileError e) 
Instance details

Defined in Cardano.Api.Error

Methods

prettyError :: FileError e -> Doc ann #

Eq e => Eq (FileError e) 
Instance details

Defined in Cardano.Api.Error

data Featured (eon :: Type -> Type) era a where #

Constructors

Featured :: forall (eon :: Type -> Type) era a. eon era -> a -> Featured eon era a 

Instances

Instances details
Functor (Featured eon era) 
Instance details

Defined in Cardano.Api.Feature

Methods

fmap :: (a -> b) -> Featured eon era a -> Featured eon era b Source #

(<$) :: a -> Featured eon era b -> Featured eon era a Source #

(Show a, Show (eon era)) => Show (Featured eon era a) 
Instance details

Defined in Cardano.Api.Feature

Methods

showsPrec :: Int -> Featured eon era a -> ShowS Source #

show :: Featured eon era a -> String Source #

showList :: [Featured eon era a] -> ShowS Source #

(Eq a, Eq (eon era)) => Eq (Featured eon era a) 
Instance details

Defined in Cardano.Api.Feature

Methods

(==) :: Featured eon era a -> Featured eon era a -> Bool Source #

(/=) :: Featured eon era a -> Featured eon era a -> Bool Source #

data ResolvablePointers where #

Constructors

ResolvablePointers :: forall era. (Era (ShelleyLedgerEra era), Show (PlutusPurpose AsIndex (ShelleyLedgerEra era)), Show (PlutusPurpose AsItem (ShelleyLedgerEra era)), Show (PlutusScript (ShelleyLedgerEra era))) => ShelleyBasedEra era -> !(Map (PlutusPurpose AsIndex (ShelleyLedgerEra era)) (PlutusPurpose AsItem (ShelleyLedgerEra era), Maybe (PlutusScriptBytes, Language), ScriptHash StandardCrypto)) -> ResolvablePointers 

data TransactionValidityError era where #

Instances

Instances details
Show (TransactionValidityError era) 
Instance details

Defined in Cardano.Api.Fees

Error (TransactionValidityError era) 
Instance details

Defined in Cardano.Api.Fees

type AlonzoGenesisFile = File AlonzoGenesisConfig #

type ByronGenesisFile = File ByronGenesisConfig #

type ConwayGenesisFile = File ConwayGenesisConfig #

type ShelleyGenesisFile = File ShelleyGenesisConfig #

class Typeable t => HasTypeProxy t where #

Associated Types

data AsType t #

Methods

proxyToAsType :: Proxy t -> AsType t #

Instances

Instances details
HasTypeProxy AddressAny 
Instance details

Defined in Cardano.Api.Address

Associated Types

data AsType AddressAny #

HasTypeProxy ByronAddr 
Instance details

Defined in Cardano.Api.Address

Associated Types

data AsType ByronAddr #

HasTypeProxy ShelleyAddr 
Instance details

Defined in Cardano.Api.Address

Associated Types

data AsType ShelleyAddr #

HasTypeProxy StakeAddress 
Instance details

Defined in Cardano.Api.Address

Associated Types

data AsType StakeAddress #

HasTypeProxy BlockHeader 
Instance details

Defined in Cardano.Api.Block

Associated Types

data AsType BlockHeader #

HasTypeProxy DRepMetadata 
Instance details

Defined in Cardano.Api.DRepMetadata

Associated Types

data AsType DRepMetadata #

HasTypeProxy AllegraEra 
Instance details

Defined in Cardano.Api.Eras.Core

Associated Types

data AsType AllegraEra #

HasTypeProxy AlonzoEra 
Instance details

Defined in Cardano.Api.Eras.Core

Associated Types

data AsType AlonzoEra #

HasTypeProxy BabbageEra 
Instance details

Defined in Cardano.Api.Eras.Core

Associated Types

data AsType BabbageEra #

HasTypeProxy ByronEra 
Instance details

Defined in Cardano.Api.Eras.Core

Associated Types

data AsType ByronEra #

HasTypeProxy ConwayEra 
Instance details

Defined in Cardano.Api.Eras.Core

Associated Types

data AsType ConwayEra #

HasTypeProxy MaryEra 
Instance details

Defined in Cardano.Api.Eras.Core

Associated Types

data AsType MaryEra #

HasTypeProxy ShelleyEra 
Instance details

Defined in Cardano.Api.Eras.Core

Associated Types

data AsType ShelleyEra #

HasTypeProxy GovernancePoll 
Instance details

Defined in Cardano.Api.Governance.Poll

Associated Types

data AsType GovernancePoll #

HasTypeProxy GovernancePollAnswer 
Instance details

Defined in Cardano.Api.Governance.Poll

Associated Types

data AsType GovernancePollAnswer #

HasTypeProxy ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

Associated Types

data AsType ByronKey #

HasTypeProxy ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

Associated Types

data AsType ByronKeyLegacy #

HasTypeProxy KesKey 
Instance details

Defined in Cardano.Api.Keys.Praos

Associated Types

data AsType KesKey #

HasTypeProxy VrfKey 
Instance details

Defined in Cardano.Api.Keys.Praos

Associated Types

data AsType VrfKey #

HasTypeProxy CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType CommitteeColdExtendedKey #

HasTypeProxy CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType CommitteeColdKey #

HasTypeProxy CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType CommitteeHotExtendedKey #

HasTypeProxy CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType CommitteeHotKey #

HasTypeProxy DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType DRepExtendedKey #

HasTypeProxy DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType DRepKey #

HasTypeProxy GenesisDelegateExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType GenesisDelegateExtendedKey #

HasTypeProxy GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType GenesisDelegateKey #

HasTypeProxy GenesisExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType GenesisExtendedKey #

HasTypeProxy GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType GenesisKey #

HasTypeProxy GenesisUTxOKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType GenesisUTxOKey #

HasTypeProxy PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType PaymentExtendedKey #

HasTypeProxy PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType PaymentKey #

HasTypeProxy StakeExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType StakeExtendedKey #

HasTypeProxy StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType StakeKey #

HasTypeProxy StakePoolKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType StakePoolKey #

HasTypeProxy OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

Associated Types

data AsType OperationalCertificate #

HasTypeProxy OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

HasTypeProxy PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Associated Types

data AsType PraosNonce #

HasTypeProxy UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

Associated Types

data AsType UpdateProposal #

HasTypeProxy PlutusScriptV1 
Instance details

Defined in Cardano.Api.Script

Associated Types

data AsType PlutusScriptV1 #

HasTypeProxy PlutusScriptV2 
Instance details

Defined in Cardano.Api.Script

Associated Types

data AsType PlutusScriptV2 #

HasTypeProxy PlutusScriptV3 
Instance details

Defined in Cardano.Api.Script

Associated Types

data AsType PlutusScriptV3 #

HasTypeProxy ScriptHash 
Instance details

Defined in Cardano.Api.Script

Associated Types

data AsType ScriptHash #

HasTypeProxy ScriptInAnyLang 
Instance details

Defined in Cardano.Api.Script

Associated Types

data AsType ScriptInAnyLang #

HasTypeProxy SimpleScript' 
Instance details

Defined in Cardano.Api.Script

Associated Types

data AsType SimpleScript' #

HasTypeProxy HashableScriptData 
Instance details

Defined in Cardano.Api.ScriptData

Associated Types

data AsType HashableScriptData #

HasTypeProxy ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

Associated Types

data AsType ScriptData #

HasTypeProxy TextEnvelope 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Associated Types

data AsType TextEnvelope #

HasTypeProxy StakePoolMetadata 
Instance details

Defined in Cardano.Api.StakePoolMetadata

Associated Types

data AsType StakePoolMetadata #

HasTypeProxy TxId 
Instance details

Defined in Cardano.Api.TxIn

Associated Types

data AsType TxId #

HasTypeProxy TxMetadata 
Instance details

Defined in Cardano.Api.TxMetadata

Associated Types

data AsType TxMetadata #

HasTypeProxy AssetName 
Instance details

Defined in Cardano.Api.Value

Associated Types

data AsType AssetName #

HasTypeProxy PolicyId 
Instance details

Defined in Cardano.Api.Value

Associated Types

data AsType PolicyId #

HasTypeProxy addrtype => HasTypeProxy (Address addrtype) 
Instance details

Defined in Cardano.Api.Address

Associated Types

data AsType (Address addrtype) #

Methods

proxyToAsType :: Proxy (Address addrtype) -> AsType (Address addrtype) #

HasTypeProxy era => HasTypeProxy (AddressInEra era) 
Instance details

Defined in Cardano.Api.Address

Associated Types

data AsType (AddressInEra era) #

Typeable era => HasTypeProxy (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

Associated Types

data AsType (Certificate era) #

HasTypeProxy era => HasTypeProxy (Proposal era) 
Instance details

Defined in Cardano.Api.Governance.Actions.ProposalProcedure

Associated Types

data AsType (Proposal era) #

Methods

proxyToAsType :: Proxy (Proposal era) -> AsType (Proposal era) #

HasTypeProxy era => HasTypeProxy (VotingProcedure era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

Associated Types

data AsType (VotingProcedure era) #

HasTypeProxy era => HasTypeProxy (VotingProcedures era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

Associated Types

data AsType (VotingProcedures era) #

HasTypeProxy a => HasTypeProxy (Hash a) 
Instance details

Defined in Cardano.Api.Hash

Associated Types

data AsType (Hash a) #

Methods

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

HasTypeProxy a => HasTypeProxy (SigningKey a) 
Instance details

Defined in Cardano.Api.Keys.Class

Associated Types

data AsType (SigningKey a) #

HasTypeProxy a => HasTypeProxy (VerificationKey a) 
Instance details

Defined in Cardano.Api.Keys.Class

Associated Types

data AsType (VerificationKey a) #

HasTypeProxy lang => HasTypeProxy (PlutusScript lang) 
Instance details

Defined in Cardano.Api.Script

Associated Types

data AsType (PlutusScript lang) #

HasTypeProxy lang => HasTypeProxy (Script lang) 
Instance details

Defined in Cardano.Api.Script

Associated Types

data AsType (Script lang) #

Methods

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

HasTypeProxy era => HasTypeProxy (ScriptInEra era) 
Instance details

Defined in Cardano.Api.Script

Associated Types

data AsType (ScriptInEra era) #

HasTypeProxy era => HasTypeProxy (KeyWitness era) 
Instance details

Defined in Cardano.Api.Tx.Sign

Associated Types

data AsType (KeyWitness era) #

Methods

proxyToAsType :: Proxy (KeyWitness era) -> AsType (KeyWitness era) #

HasTypeProxy era => HasTypeProxy (Tx era) 
Instance details

Defined in Cardano.Api.Tx.Sign

Associated Types

data AsType (Tx era) #

Methods

proxyToAsType :: Proxy (Tx era) -> AsType (Tx era) #

HasTypeProxy era => HasTypeProxy (TxBody era) 
Instance details

Defined in Cardano.Api.Tx.Sign

Associated Types

data AsType (TxBody era) #

Methods

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

data family AsType t #

Instances

Instances details
data AsType AddressAny 
Instance details

Defined in Cardano.Api.Address

data AsType ByronAddr 
Instance details

Defined in Cardano.Api.Address

data AsType ShelleyAddr 
Instance details

Defined in Cardano.Api.Address

data AsType StakeAddress 
Instance details

Defined in Cardano.Api.Address

data AsType BlockHeader 
Instance details

Defined in Cardano.Api.Block

data AsType DRepMetadata 
Instance details

Defined in Cardano.Api.DRepMetadata

data AsType AllegraEra 
Instance details

Defined in Cardano.Api.Eras.Core

data AsType AlonzoEra 
Instance details

Defined in Cardano.Api.Eras.Core

data AsType BabbageEra 
Instance details

Defined in Cardano.Api.Eras.Core

data AsType ByronEra 
Instance details

Defined in Cardano.Api.Eras.Core

data AsType ConwayEra 
Instance details

Defined in Cardano.Api.Eras.Core

data AsType MaryEra 
Instance details

Defined in Cardano.Api.Eras.Core

data AsType ShelleyEra 
Instance details

Defined in Cardano.Api.Eras.Core

data AsType GovernancePoll 
Instance details

Defined in Cardano.Api.Governance.Poll

data AsType GovernancePollAnswer 
Instance details

Defined in Cardano.Api.Governance.Poll

data AsType ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

data AsType ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

data AsType KesKey 
Instance details

Defined in Cardano.Api.Keys.Praos

data AsType VrfKey 
Instance details

Defined in Cardano.Api.Keys.Praos

data AsType CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType GenesisDelegateExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType GenesisExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType GenesisUTxOKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType StakeExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType StakePoolKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

data AsType OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

data AsType PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

data AsType UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

data AsType PlutusScriptV1 
Instance details

Defined in Cardano.Api.Script

data AsType PlutusScriptV2 
Instance details

Defined in Cardano.Api.Script

data AsType PlutusScriptV3 
Instance details

Defined in Cardano.Api.Script

data AsType ScriptHash 
Instance details

Defined in Cardano.Api.Script

data AsType ScriptInAnyLang 
Instance details

Defined in Cardano.Api.Script

data AsType SimpleScript' 
Instance details

Defined in Cardano.Api.Script

data AsType HashableScriptData 
Instance details

Defined in Cardano.Api.ScriptData

data AsType ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

data AsType TextEnvelope 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

data AsType StakePoolMetadata 
Instance details

Defined in Cardano.Api.StakePoolMetadata

data AsType TxId 
Instance details

Defined in Cardano.Api.TxIn

data AsType TxMetadata 
Instance details

Defined in Cardano.Api.TxMetadata

data AsType AssetName 
Instance details

Defined in Cardano.Api.Value

data AsType PolicyId 
Instance details

Defined in Cardano.Api.Value

data AsType (Address addrtype) 
Instance details

Defined in Cardano.Api.Address

data AsType (Address addrtype) = AsAddress (AsType addrtype)
data AsType (AddressInEra era) 
Instance details

Defined in Cardano.Api.Address

data AsType (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

data AsType (Proposal era) 
Instance details

Defined in Cardano.Api.Governance.Actions.ProposalProcedure

data AsType (VotingProcedure era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

data AsType (VotingProcedures era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

data AsType (Hash a) 
Instance details

Defined in Cardano.Api.Hash

data AsType (Hash a) = AsHash (AsType a)
data AsType (SigningKey a) 
Instance details

Defined in Cardano.Api.Keys.Class

data AsType (VerificationKey a) 
Instance details

Defined in Cardano.Api.Keys.Class

data AsType (PlutusScript lang) 
Instance details

Defined in Cardano.Api.Script

data AsType (Script lang) 
Instance details

Defined in Cardano.Api.Script

data AsType (Script lang) = AsScript (AsType lang)
data AsType (ScriptInEra era) 
Instance details

Defined in Cardano.Api.Script

data AsType (KeyWitness era) 
Instance details

Defined in Cardano.Api.Tx.Sign

data AsType (Tx era) 
Instance details

Defined in Cardano.Api.Tx.Sign

data AsType (Tx era) = AsTx (AsType era)
data AsType (TxBody era) 
Instance details

Defined in Cardano.Api.Tx.Sign

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

class AsTxMetadata a where #

Methods

asTxMetadata :: a -> TxMetadata #

data FromSomeType (c :: Type -> Constraint) b where #

Constructors

FromSomeType :: forall (c :: Type -> Constraint) a b. c a => AsType a -> (a -> b) -> FromSomeType c b 

data FileDirection #

Constructors

In 
Out 
InOut 

type SocketPath = File Socket 'InOut #

data LocalChainSyncClient block point tip (m :: Type -> Type) #

data LocalNodeClientParams where #

Constructors

LocalNodeClientParamsSingleBlock :: forall block. (ProtocolClient block, LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))) => ProtocolClientInfoArgs block -> (NodeToClientVersion -> LocalNodeClientProtocolsForBlock block) -> LocalNodeClientParams 
LocalNodeClientParamsCardano :: forall block. (ProtocolClient block, CardanoHardForkConstraints (ConsensusCryptoForBlock block)) => ProtocolClientInfoArgs block -> (NodeToClientVersion -> LocalNodeClientProtocolsForBlock block) -> LocalNodeClientParams 

data LocalNodeClientProtocols block point tip slot tx txid txerr (query :: Type -> Type) (m :: Type -> Type) #

data LocalStateQueryExpr block point (query :: Type -> Type) r (m :: Type -> Type) a #

Instances

Instances details
MonadReader NodeToClientVersion (LocalStateQueryExpr block point query r m) 
Instance details

Defined in Cardano.Api.IPC.Monad

Methods

ask :: LocalStateQueryExpr block point query r m NodeToClientVersion Source #

local :: (NodeToClientVersion -> NodeToClientVersion) -> LocalStateQueryExpr block point query r m a -> LocalStateQueryExpr block point query r m a Source #

reader :: (NodeToClientVersion -> a) -> LocalStateQueryExpr block point query r m a Source #

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

Defined in Cardano.Api.IPC.Monad

Methods

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

Applicative (LocalStateQueryExpr block point query r m) 
Instance details

Defined in Cardano.Api.IPC.Monad

Methods

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

(<*>) :: LocalStateQueryExpr block point query r m (a -> b) -> LocalStateQueryExpr block point query r m a -> LocalStateQueryExpr block point query r m b Source #

liftA2 :: (a -> b -> c) -> LocalStateQueryExpr block point query r m a -> LocalStateQueryExpr block point query r m b -> LocalStateQueryExpr block point query r m c Source #

(*>) :: LocalStateQueryExpr block point query r m a -> LocalStateQueryExpr block point query r m b -> LocalStateQueryExpr block point query r m b Source #

(<*) :: LocalStateQueryExpr block point query r m a -> LocalStateQueryExpr block point query r m b -> LocalStateQueryExpr block point query r m a Source #

Functor (LocalStateQueryExpr block point query r m) 
Instance details

Defined in Cardano.Api.IPC.Monad

Methods

fmap :: (a -> b) -> LocalStateQueryExpr block point query r m a -> LocalStateQueryExpr block point query r m b Source #

(<$) :: a -> LocalStateQueryExpr block point query r m b -> LocalStateQueryExpr block point query r m a Source #

Monad (LocalStateQueryExpr block point query r m) 
Instance details

Defined in Cardano.Api.IPC.Monad

Methods

(>>=) :: LocalStateQueryExpr block point query r m a -> (a -> LocalStateQueryExpr block point query r m b) -> LocalStateQueryExpr block point query r m b Source #

(>>) :: LocalStateQueryExpr block point query r m a -> LocalStateQueryExpr block point query r m b -> LocalStateQueryExpr block point query r m b Source #

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

data TxIdInMode where #

Constructors

TxIdInMode :: forall era. CardanoEra era -> TxId -> TxIdInMode 

data TxInMode where #

Constructors

TxInMode :: forall era. ShelleyBasedEra era -> Tx era -> TxInMode 
TxInByronSpecial :: GenTx ByronBlock -> TxInMode 

Instances

Instances details
Show TxInMode 
Instance details

Defined in Cardano.Api.InMode

data ByronKey #

Instances

Instances details
HasTypeProxy ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

Associated Types

data AsType ByronKey #

IsByronKey ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

byronKeyFormat :: ByronKeyFormat ByronKey

Key ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

Associated Types

data VerificationKey ByronKey #

data SigningKey ByronKey #

CastVerificationKeyRole ByronKey PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Byron

CastVerificationKeyRole ByronKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Byron

CastVerificationKeyRole ByronKeyLegacy ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

IsString (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

IsString (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

IsString (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Show (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Show (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Show (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

HasTextEnvelope (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

HasTextEnvelope (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

fromCBOR :: Decoder s (Hash ByronKey)

label :: Proxy (Hash ByronKey) -> Text

FromCBOR (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

ToCBOR (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: Hash ByronKey -> Encoding

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

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

ToCBOR (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: SigningKey ByronKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey ByronKey) -> Size

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

ToCBOR (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: VerificationKey ByronKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey ByronKey) -> Size

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

Eq (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Eq (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

Ord (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

data AsType ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

newtype Hash ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

newtype Hash ByronKey = ByronKeyHash KeyHash
newtype SigningKey ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

newtype SigningKey ByronKey = ByronSigningKey SigningKey
newtype VerificationKey ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

data ByronKeyLegacy #

Instances

Instances details
HasTypeProxy ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

Associated Types

data AsType ByronKeyLegacy #

IsByronKey ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

byronKeyFormat :: ByronKeyFormat ByronKeyLegacy

Key ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

CastVerificationKeyRole ByronKeyLegacy ByronKey 
Instance details

Defined in Cardano.Api.Keys.Byron

IsString (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

IsString (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

IsString (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Show (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Show (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Show (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

HasTextEnvelope (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

HasTextEnvelope (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

FromCBOR (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

ToCBOR (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: Hash ByronKeyLegacy -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash ByronKeyLegacy) -> Size

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

ToCBOR (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: SigningKey ByronKeyLegacy -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey ByronKeyLegacy) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey ByronKeyLegacy] -> Size

ToCBOR (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Methods

toCBOR :: VerificationKey ByronKeyLegacy -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey ByronKeyLegacy) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey ByronKeyLegacy] -> Size

Eq (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Eq (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

Ord (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

data AsType ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

newtype Hash ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

newtype SigningKey ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

newtype VerificationKey ByronKeyLegacy 
Instance details

Defined in Cardano.Api.Keys.Byron

data CommitteeColdExtendedKey #

Instances

Instances details
HasTypeProxy CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType CommitteeColdExtendedKey #

Key CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole CommitteeColdExtendedKey CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash CommitteeColdExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeColdExtendedKey) -> Size

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

ToCBOR (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey CommitteeColdExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdExtendedKey] -> Size

ToCBOR (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey CommitteeColdExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data CommitteeColdKey #

Instances

Instances details
HasTypeProxy CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType CommitteeColdKey #

Key CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole CommitteeColdExtendedKey CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole CommitteeColdKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash CommitteeColdKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeColdKey) -> Size

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

ToCBOR (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey CommitteeColdKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeColdKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeColdKey] -> Size

ToCBOR (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey CommitteeColdKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeColdKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeColdKey] -> Size

Eq (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey CommitteeColdKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data CommitteeHotExtendedKey #

Instances

Instances details
HasTypeProxy CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType CommitteeHotExtendedKey #

Key CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole CommitteeHotExtendedKey CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash CommitteeHotExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeHotExtendedKey) -> Size

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

ToCBOR (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey CommitteeHotExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotExtendedKey] -> Size

ToCBOR (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey CommitteeHotExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data CommitteeHotKey #

Instances

Instances details
HasTypeProxy CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType CommitteeHotKey #

Key CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole CommitteeHotExtendedKey CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole CommitteeHotKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash CommitteeHotKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash CommitteeHotKey) -> Size

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

ToCBOR (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey CommitteeHotKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey CommitteeHotKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey CommitteeHotKey] -> Size

ToCBOR (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey CommitteeHotKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey CommitteeHotKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey CommitteeHotKey] -> Size

Eq (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey CommitteeHotKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data DRepExtendedKey #

Instances

Instances details
HasTypeProxy DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType DRepExtendedKey #

Key DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole DRepExtendedKey DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash DRepExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash DRepExtendedKey) -> Size

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

ToCBOR (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey DRepExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey DRepExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey DRepExtendedKey] -> Size

ToCBOR (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey DRepExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey DRepExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey DRepExtendedKey] -> Size

Eq (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey DRepExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data DRepKey #

Instances

Instances details
HasTypeProxy DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType DRepKey #

Key DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data VerificationKey DRepKey #

data SigningKey DRepKey #

CastVerificationKeyRole DRepExtendedKey DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromJSON (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

parseJSON :: Value -> Parser (Hash DRepKey) #

parseJSONList :: Value -> Parser [Hash DRepKey] #

omittedField :: Maybe (Hash DRepKey) #

ToJSON (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toJSON :: Hash DRepKey -> Value #

toEncoding :: Hash DRepKey -> Encoding #

toJSONList :: [Hash DRepKey] -> Value #

toEncodingList :: [Hash DRepKey] -> Encoding #

omitField :: Hash DRepKey -> Bool #

ToJSONKey (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toJSONKey :: ToJSONKeyFunction (Hash DRepKey)

toJSONKeyList :: ToJSONKeyFunction [Hash DRepKey]

IsString (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash DRepKey)

label :: Proxy (Hash DRepKey) -> Text

FromCBOR (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash DRepKey -> Encoding

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

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

ToCBOR (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey DRepKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey DRepKey) -> Size

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

ToCBOR (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey DRepKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey DRepKey) -> Size

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

Eq (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash DRepKey = DRepKeyHash {}
newtype SigningKey DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey DRepKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data GenesisDelegateExtendedKey #

Instances

Instances details
HasTypeProxy GenesisDelegateExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType GenesisDelegateExtendedKey #

Key GenesisDelegateExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole GenesisDelegateExtendedKey GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisDelegateExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisDelegateExtendedKey) -> Size

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

ToCBOR (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisDelegateExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateExtendedKey] -> Size

ToCBOR (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType GenesisDelegateExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash GenesisDelegateExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey GenesisDelegateExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey GenesisDelegateExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data GenesisDelegateKey #

Instances

Instances details
HasTypeProxy GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType GenesisDelegateKey #

Key GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastSigningKeyRole GenesisDelegateKey StakePoolKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole GenesisDelegateExtendedKey GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole GenesisDelegateKey StakePoolKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisDelegateKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisDelegateKey) -> Size

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

ToCBOR (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisDelegateKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisDelegateKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisDelegateKey] -> Size

ToCBOR (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey GenesisDelegateKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisDelegateKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisDelegateKey] -> Size

Eq (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey GenesisDelegateKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data GenesisExtendedKey #

Instances

Instances details
HasTypeProxy GenesisExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType GenesisExtendedKey #

Key GenesisExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole GenesisExtendedKey GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisExtendedKey) -> Size

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

ToCBOR (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisExtendedKey] -> Size

ToCBOR (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey GenesisExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisExtendedKey] -> Size

Eq (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType GenesisExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash GenesisExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey GenesisExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey GenesisExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data GenesisKey #

Instances

Instances details
HasTypeProxy GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType GenesisKey #

Key GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole GenesisExtendedKey GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole GenesisKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromJSON (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

parseJSON :: Value -> Parser (Hash GenesisKey) #

parseJSONList :: Value -> Parser [Hash GenesisKey] #

omittedField :: Maybe (Hash GenesisKey) #

ToJSON (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toJSON :: Hash GenesisKey -> Value #

toEncoding :: Hash GenesisKey -> Encoding #

toJSONList :: [Hash GenesisKey] -> Value #

toEncodingList :: [Hash GenesisKey] -> Encoding #

omitField :: Hash GenesisKey -> Bool #

ToJSONKey (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toJSONKey :: ToJSONKeyFunction (Hash GenesisKey)

toJSONKeyList :: ToJSONKeyFunction [Hash GenesisKey]

IsString (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash GenesisKey)

label :: Proxy (Hash GenesisKey) -> Text

FromCBOR (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisKey) -> Size

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

ToCBOR (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisKey] -> Size

ToCBOR (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey GenesisKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisKey] -> Size

Eq (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey GenesisKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data GenesisUTxOKey #

Instances

Instances details
HasTypeProxy GenesisUTxOKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType GenesisUTxOKey #

Key GenesisUTxOKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastSigningKeyRole GenesisUTxOKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole GenesisUTxOKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash GenesisUTxOKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash GenesisUTxOKey) -> Size

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

ToCBOR (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey GenesisUTxOKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey GenesisUTxOKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey GenesisUTxOKey] -> Size

ToCBOR (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey GenesisUTxOKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey GenesisUTxOKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey GenesisUTxOKey] -> Size

Eq (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType GenesisUTxOKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash GenesisUTxOKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey GenesisUTxOKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey GenesisUTxOKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data PaymentExtendedKey #

Instances

Instances details
HasTypeProxy PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType PaymentExtendedKey #

Key PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole ByronKey PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Byron

CastVerificationKeyRole PaymentExtendedKey PaymentKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash PaymentExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash PaymentExtendedKey) -> Size

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

ToCBOR (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey PaymentExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey PaymentExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey PaymentExtendedKey] -> Size

ToCBOR (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey PaymentExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey PaymentExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey PaymentExtendedKey] -> Size

Eq (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey PaymentExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data StakeExtendedKey #

Instances

Instances details
HasTypeProxy StakeExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType StakeExtendedKey #

Key StakeExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole StakeExtendedKey StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash StakeExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (Hash StakeExtendedKey) -> Size

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

ToCBOR (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey StakeExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakeExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [SigningKey StakeExtendedKey] -> Size

ToCBOR (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey StakeExtendedKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakeExtendedKey) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [VerificationKey StakeExtendedKey] -> Size

Eq (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType StakeExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash StakeExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype SigningKey StakeExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey StakeExtendedKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data StakeKey #

Instances

Instances details
HasTypeProxy StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data AsType StakeKey #

Key StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

Associated Types

data VerificationKey StakeKey #

data SigningKey StakeKey #

CastVerificationKeyRole StakeExtendedKey StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

CastVerificationKeyRole StakePoolKey StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsString (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Show (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

fromCBOR :: Decoder s (Hash StakeKey)

label :: Proxy (Hash StakeKey) -> Text

FromCBOR (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

FromCBOR (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

ToCBOR (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: Hash StakeKey -> Encoding

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

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

ToCBOR (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: SigningKey StakeKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (SigningKey StakeKey) -> Size

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

ToCBOR (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Methods

toCBOR :: VerificationKey StakeKey -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (VerificationKey StakeKey) -> Size

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

Eq (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Eq (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

Ord (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AsType StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype Hash StakeKey = StakeKeyHash {}
newtype SigningKey StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

newtype VerificationKey StakeKey 
Instance details

Defined in Cardano.Api.Keys.Shelley

data AnyNewEpochState where #

Constructors

AnyNewEpochState :: forall era. ShelleyBasedEra era -> NewEpochState (ShelleyLedgerEra era) -> AnyNewEpochState 

data FoldStatus #

Instances

Instances details
Show FoldStatus 
Instance details

Defined in Cardano.Api.LedgerState

Eq FoldStatus 
Instance details

Defined in Cardano.Api.LedgerState

data GenesisConfig #

Constructors

GenesisCardano !NodeConfig !Config !GenesisHashShelley !(TransitionConfig (LatestKnownEra StandardCrypto)) 

newtype LedgerState #

Constructors

LedgerState 

Fields

Bundled Patterns

pattern LedgerStateAllegra :: () => LedgerState (ShelleyBlock protocol (AllegraEra StandardCrypto)) -> LedgerState 
pattern LedgerStateAlonzo :: () => LedgerState (ShelleyBlock protocol (AlonzoEra StandardCrypto)) -> LedgerState 
pattern LedgerStateBabbage :: () => LedgerState (ShelleyBlock protocol (BabbageEra StandardCrypto)) -> LedgerState 
pattern LedgerStateByron :: LedgerState ByronBlock -> LedgerState 
pattern LedgerStateConway :: () => LedgerState (ShelleyBlock protocol (ConwayEra StandardCrypto)) -> LedgerState 
pattern LedgerStateMary :: () => LedgerState (ShelleyBlock protocol (MaryEra StandardCrypto)) -> LedgerState 
pattern LedgerStateShelley :: () => LedgerState (ShelleyBlock protocol (ShelleyEra StandardCrypto)) -> LedgerState 

Instances

Instances details
Show LedgerState 
Instance details

Defined in Cardano.Api.LedgerState

data NodeConfig #

Constructors

NodeConfig 

Fields

Instances

Instances details
FromJSON NodeConfig 
Instance details

Defined in Cardano.Api.LedgerState

Methods

parseJSON :: Value -> Parser NodeConfig #

parseJSONList :: Value -> Parser [NodeConfig] #

omittedField :: Maybe NodeConfig #

type family ConsensusBlockForEra era where ... #

Equations

ConsensusBlockForEra ByronEra = ByronBlock 
ConsensusBlockForEra ShelleyEra = StandardShelleyBlock 
ConsensusBlockForEra AllegraEra = StandardAllegraBlock 
ConsensusBlockForEra MaryEra = StandardMaryBlock 
ConsensusBlockForEra AlonzoEra = StandardAlonzoBlock 
ConsensusBlockForEra BabbageEra = StandardBabbageBlock 
ConsensusBlockForEra ConwayEra = StandardConwayBlock 

type MonadIOTransError e (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) = (MonadIO m, MonadIO (t m), MonadCatch m, MonadTrans t, MonadError e (t m)) #

type MonadTransError e (t :: (Type -> Type) -> Type -> Type) (m :: Type -> Type) = (Monad m, MonadTrans t, MonadError e (t m)) #

data OperationalCertificate #

Instances

Instances details
Show OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

HasTypeProxy OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

Associated Types

data AsType OperationalCertificate #

SerialiseAsCBOR OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

HasTextEnvelope OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

FromCBOR OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

ToCBOR OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

Methods

toCBOR :: OperationalCertificate -> Encoding

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

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

Eq OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

data AsType OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

data OperationalCertificateIssueCounter #

Instances

Instances details
Show OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

HasTypeProxy OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

SerialiseAsCBOR OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

HasTextEnvelope OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

FromCBOR OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

ToCBOR OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

Eq OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

data AsType OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

type Ann = AnsiStyle #

data BlockType blk where #

Constructors

ByronBlockType :: BlockType (HardForkBlock '[ByronBlock]) 
ShelleyBlockType :: BlockType (HardForkBlock '[ShelleyBlock (TPraos StandardCrypto) StandardShelley]) 
CardanoBlockType :: BlockType (HardForkBlock (CardanoEras StandardCrypto)) 

Instances

Instances details
Show (BlockType blk) 
Instance details

Defined in Cardano.Api.Protocol

Eq (BlockType blk) 
Instance details

Defined in Cardano.Api.Protocol

Methods

(==) :: BlockType blk -> BlockType blk -> Bool Source #

(/=) :: BlockType blk -> BlockType blk -> Bool Source #

class (RunNode blk, IOLike m) => Protocol (m :: Type -> Type) blk where #

Associated Types

data ProtocolInfoArgs blk #

Methods

protocolInfo :: ProtocolInfoArgs blk -> (ProtocolInfo blk, m [BlockForging m blk]) #

Instances

Instances details
IOLike m => Protocol m ByronBlockHFC 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolInfoArgs ByronBlockHFC #

Methods

protocolInfo :: ProtocolInfoArgs ByronBlockHFC -> (ProtocolInfo ByronBlockHFC, m [BlockForging m ByronBlockHFC]) #

(CardanoHardForkConstraints StandardCrypto, IOLike m) => Protocol m (CardanoBlock StandardCrypto) 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolInfoArgs (CardanoBlock StandardCrypto) #

Methods

protocolInfo :: ProtocolInfoArgs (CardanoBlock StandardCrypto) -> (ProtocolInfo (CardanoBlock StandardCrypto), m [BlockForging m (CardanoBlock StandardCrypto)]) #

(IOLike m, LedgerSupportsProtocol (ShelleyBlock (TPraos StandardCrypto) (ShelleyEra StandardCrypto))) => Protocol m (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) 
Instance details

Defined in Cardano.Api.Protocol

Associated Types

data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) #

Methods

protocolInfo :: ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) -> (ProtocolInfo (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley), m [BlockForging m (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley)]) #

data family ProtocolInfoArgs blk #

Instances

Instances details
data ProtocolInfoArgs ByronBlockHFC 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolInfoArgs ByronBlockHFC = ProtocolInfoArgsByron (ProtocolParams ByronBlock)
data ProtocolInfoArgs (CardanoBlock StandardCrypto) 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolInfoArgs (CardanoBlock StandardCrypto) = ProtocolInfoArgsCardano (CardanoProtocolParams StandardCrypto)
data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) 
Instance details

Defined in Cardano.Api.Protocol

data ProtocolInfoArgs (ShelleyBlockHFC (TPraos StandardCrypto) StandardShelley) = ProtocolInfoArgsShelley (ShelleyGenesis StandardCrypto) (ProtocolParamsShelleyBased StandardCrypto) (ProtocolParams (ShelleyBlock (TPraos StandardCrypto) StandardShelley))

data SomeBlockType where #

Constructors

SomeBlockType :: forall blk. BlockType blk -> SomeBlockType 

Instances

Instances details
Show SomeBlockType 
Instance details

Defined in Cardano.Api.Protocol

newtype CostModel #

Constructors

CostModel [Integer] 

Instances

Instances details
Data CostModel 
Instance details

Defined in Cardano.Api.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 
Instance details

Defined in Cardano.Api.ProtocolParameters

FromCBOR CostModel 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

fromCBOR :: Decoder s CostModel

label :: Proxy CostModel -> Text

ToCBOR CostModel 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toCBOR :: CostModel -> Encoding

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

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

Eq CostModel 
Instance details

Defined in Cardano.Api.ProtocolParameters

data ExecutionUnitPrices #

Instances

Instances details
FromJSON ExecutionUnitPrices 
Instance details

Defined in Cardano.Api.ProtocolParameters

ToJSON ExecutionUnitPrices 
Instance details

Defined in Cardano.Api.ProtocolParameters

Show ExecutionUnitPrices 
Instance details

Defined in Cardano.Api.ProtocolParameters

FromCBOR ExecutionUnitPrices 
Instance details

Defined in Cardano.Api.ProtocolParameters

ToCBOR ExecutionUnitPrices 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toCBOR :: ExecutionUnitPrices -> Encoding

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

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

Eq ExecutionUnitPrices 
Instance details

Defined in Cardano.Api.ProtocolParameters

data PraosNonce #

Instances

Instances details
FromJSON PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

parseJSON :: Value -> Parser PraosNonce #

parseJSONList :: Value -> Parser [PraosNonce] #

omittedField :: Maybe PraosNonce #

ToJSON PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toJSON :: PraosNonce -> Value #

toEncoding :: PraosNonce -> Encoding #

toJSONList :: [PraosNonce] -> Value #

toEncodingList :: [PraosNonce] -> Encoding #

omitField :: PraosNonce -> Bool #

IsString PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Generic PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Associated Types

type Rep PraosNonce :: Type -> Type Source #

Show PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

HasTypeProxy PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Associated Types

data AsType PraosNonce #

SerialiseAsRawBytes PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

FromCBOR PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

fromCBOR :: Decoder s PraosNonce

label :: Proxy PraosNonce -> Text

ToCBOR PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toCBOR :: PraosNonce -> Encoding

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

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

Eq PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

Ord PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

type Rep PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

type Rep PraosNonce = D1 ('MetaData "PraosNonce" "Cardano.Api.ProtocolParameters" "cardano-api-8.42.0.0-dXRaVskXAtCMoDkAxRwdo-internal" 'True) (C1 ('MetaCons "PraosNonce" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPraosNonce") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash StandardCrypto ByteString))))
data AsType PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

data ProtocolParametersConversionError #

Constructors

PpceOutOfBounds !ProtocolParameterName !Rational 
PpceVersionInvalid !ProtocolParameterVersion 
PpceInvalidCostModel !CostModel !CostModelApplyError 
PpceMissingParameter !ProtocolParameterName 

Instances

Instances details
Data ProtocolParametersConversionError 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProtocolParametersConversionError -> c ProtocolParametersConversionError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ProtocolParametersConversionError Source #

toConstr :: ProtocolParametersConversionError -> Constr Source #

dataTypeOf :: ProtocolParametersConversionError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ProtocolParametersConversionError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ProtocolParametersConversionError) Source #

gmapT :: (forall b. Data b => b -> b) -> ProtocolParametersConversionError -> ProtocolParametersConversionError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProtocolParametersConversionError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProtocolParametersConversionError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ProtocolParametersConversionError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProtocolParametersConversionError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProtocolParametersConversionError -> m ProtocolParametersConversionError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtocolParametersConversionError -> m ProtocolParametersConversionError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProtocolParametersConversionError -> m ProtocolParametersConversionError Source #

Show ProtocolParametersConversionError 
Instance details

Defined in Cardano.Api.ProtocolParameters

Error ProtocolParametersConversionError 
Instance details

Defined in Cardano.Api.ProtocolParameters

Eq ProtocolParametersConversionError 
Instance details

Defined in Cardano.Api.ProtocolParameters

data ProtocolParametersUpdate #

Instances

Instances details
Monoid ProtocolParametersUpdate 
Instance details

Defined in Cardano.Api.ProtocolParameters

Semigroup ProtocolParametersUpdate 
Instance details

Defined in Cardano.Api.ProtocolParameters

Show ProtocolParametersUpdate 
Instance details

Defined in Cardano.Api.ProtocolParameters

FromCBOR ProtocolParametersUpdate 
Instance details

Defined in Cardano.Api.ProtocolParameters

ToCBOR ProtocolParametersUpdate 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toCBOR :: ProtocolParametersUpdate -> Encoding

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

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

Eq ProtocolParametersUpdate 
Instance details

Defined in Cardano.Api.ProtocolParameters

data UpdateProposal #

Instances

Instances details
Show UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

HasTypeProxy UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

Associated Types

data AsType UpdateProposal #

SerialiseAsCBOR UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

HasTextEnvelope UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

FromCBOR UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

ToCBOR UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

Methods

toCBOR :: UpdateProposal -> Encoding

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

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

Eq UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

data AsType UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

data EraHistory where #

Constructors

EraHistory :: forall (xs :: [Type]). CardanoBlock StandardCrypto ~ HardForkBlock xs => Interpreter xs -> EraHistory 

newtype LedgerEpochInfo #

Constructors

LedgerEpochInfo 

Fields

data QueryInEra era result where #

Constructors

QueryByronUpdateState :: QueryInEra ByronEra ByronUpdateState 
QueryInShelleyBasedEra :: forall era result. ShelleyBasedEra era -> QueryInShelleyBasedEra era result -> QueryInEra era result 

Instances

Instances details
Show (QueryInEra era result) 
Instance details

Defined in Cardano.Api.Query

Methods

showsPrec :: Int -> QueryInEra era result -> ShowS Source #

show :: QueryInEra era result -> String Source #

showList :: [QueryInEra era result] -> ShowS Source #

NodeToClientVersionOf (QueryInEra era result) 
Instance details

Defined in Cardano.Api.Query

data QueryInShelleyBasedEra era result where #

Constructors

QueryEpoch :: forall era. QueryInShelleyBasedEra era EpochNo 
QueryGenesisParameters :: forall era. QueryInShelleyBasedEra era (GenesisParameters ShelleyEra) 
QueryProtocolParameters :: forall era. QueryInShelleyBasedEra era (PParams (ShelleyLedgerEra era)) 
QueryProtocolParametersUpdate :: forall era. QueryInShelleyBasedEra era (Map (Hash GenesisKey) ProtocolParametersUpdate) 
QueryStakeDistribution :: forall era. QueryInShelleyBasedEra era (Map (Hash StakePoolKey) Rational) 
QueryUTxO :: forall era. QueryUTxOFilter -> QueryInShelleyBasedEra era (UTxO era) 
QueryStakeAddresses :: forall era. Set StakeCredential -> NetworkId -> QueryInShelleyBasedEra era (Map StakeAddress Coin, Map StakeAddress PoolId) 
QueryStakePools :: forall era. QueryInShelleyBasedEra era (Set PoolId) 
QueryStakePoolParameters :: forall era. Set PoolId -> QueryInShelleyBasedEra era (Map PoolId StakePoolParameters) 
QueryDebugLedgerState :: forall era. QueryInShelleyBasedEra era (SerialisedDebugLedgerState era) 
QueryProtocolState :: forall era. QueryInShelleyBasedEra era (ProtocolState era) 
QueryCurrentEpochState :: forall era. QueryInShelleyBasedEra era (SerialisedCurrentEpochState era) 
QueryPoolState :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolState era) 
QueryPoolDistribution :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedPoolDistribution era) 
QueryStakeSnapshot :: forall era. Maybe (Set PoolId) -> QueryInShelleyBasedEra era (SerialisedStakeSnapshots era) 
QueryStakeDelegDeposits :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential Coin) 
QueryConstitution :: forall era. QueryInShelleyBasedEra era (Maybe (Constitution (ShelleyLedgerEra era))) 
QueryGovState :: forall era. QueryInShelleyBasedEra era (GovState (ShelleyLedgerEra era)) 
QueryDRepState :: forall era. Set (Credential 'DRepRole StandardCrypto) -> QueryInShelleyBasedEra era (Map (Credential 'DRepRole StandardCrypto) (DRepState StandardCrypto)) 
QueryDRepStakeDistr :: forall era. Set (DRep StandardCrypto) -> QueryInShelleyBasedEra era (Map (DRep StandardCrypto) Coin) 
QueryCommitteeMembersState :: forall era. Set (Credential 'ColdCommitteeRole StandardCrypto) -> Set (Credential 'HotCommitteeRole StandardCrypto) -> Set MemberStatus -> QueryInShelleyBasedEra era (Maybe (CommitteeMembersState StandardCrypto)) 
QueryStakeVoteDelegatees :: forall era. Set StakeCredential -> QueryInShelleyBasedEra era (Map StakeCredential (DRep StandardCrypto)) 

Instances

Instances details
Show (QueryInShelleyBasedEra era result) 
Instance details

Defined in Cardano.Api.Query

NodeToClientVersionOf (QueryInShelleyBasedEra era result) 
Instance details

Defined in Cardano.Api.Query

data QueryInMode result where #

Instances

Instances details
Show (QueryInMode result) 
Instance details

Defined in Cardano.Api.Query

Methods

showsPrec :: Int -> QueryInMode result -> ShowS Source #

show :: QueryInMode result -> String Source #

showList :: [QueryInMode result] -> ShowS Source #

NodeToClientVersionOf (QueryInMode result) 
Instance details

Defined in Cardano.Api.Query

newtype SlotsInEpoch #

Constructors

SlotsInEpoch Word64 

data AnyPlutusScriptVersion where #

Instances

Instances details
FromJSON AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

FromJSONKey AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

Methods

fromJSONKey :: FromJSONKeyFunction AnyPlutusScriptVersion

fromJSONKeyList :: FromJSONKeyFunction [AnyPlutusScriptVersion]

ToJSON AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

ToJSONKey AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

Methods

toJSONKey :: ToJSONKeyFunction AnyPlutusScriptVersion

toJSONKeyList :: ToJSONKeyFunction [AnyPlutusScriptVersion]

Bounded AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

Enum AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

Show AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

FromCBOR AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

ToCBOR AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

Methods

toCBOR :: AnyPlutusScriptVersion -> Encoding

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

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

Eq AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

Ord AnyPlutusScriptVersion 
Instance details

Defined in Cardano.Api.Script

data AnyScriptLanguage where #

Constructors

AnyScriptLanguage :: forall lang. ScriptLanguage lang -> AnyScriptLanguage 

Instances

Instances details
Bounded AnyScriptLanguage 
Instance details

Defined in Cardano.Api.Script

Enum AnyScriptLanguage 
Instance details

Defined in Cardano.Api.Script

Show AnyScriptLanguage 
Instance details

Defined in Cardano.Api.Script

Eq AnyScriptLanguage 
Instance details

Defined in Cardano.Api.Script

Ord AnyScriptLanguage 
Instance details

Defined in Cardano.Api.Script

data KeyWitnessInCtx witctx where #

Instances

Instances details
Show (KeyWitnessInCtx witctx) 
Instance details

Defined in Cardano.Api.Script

Eq (KeyWitnessInCtx witctx) 
Instance details

Defined in Cardano.Api.Script

Methods

(==) :: KeyWitnessInCtx witctx -> KeyWitnessInCtx witctx -> Bool Source #

(/=) :: KeyWitnessInCtx witctx -> KeyWitnessInCtx witctx -> Bool Source #

data PlutusScriptV1 #

Instances

Instances details
HasTypeProxy PlutusScriptV1 
Instance details

Defined in Cardano.Api.Script

Associated Types

data AsType PlutusScriptV1 #

IsPlutusScriptLanguage PlutusScriptV1 
Instance details

Defined in Cardano.Api.Script

IsScriptLanguage PlutusScriptV1 
Instance details

Defined in Cardano.Api.Script

HasScriptLanguageInEra PlutusScriptV1 AlonzoEra 
Instance details

Defined in Cardano.Api.Class.HasScriptLanguageInEra

HasScriptLanguageInEra PlutusScriptV1 BabbageEra 
Instance details

Defined in Cardano.Api.Class.HasScriptLanguageInEra

HasScriptLanguageInEra PlutusScriptV1 ConwayEra 
Instance details

Defined in Cardano.Api.Class.HasScriptLanguageInEra

ToAlonzoScript PlutusScriptV1 BabbageEra 
Instance details

Defined in Cardano.Api.Class.ToAlonzoScript

ToAlonzoScript PlutusScriptV1 ConwayEra 
Instance details

Defined in Cardano.Api.Class.ToAlonzoScript

data AsType PlutusScriptV1 
Instance details

Defined in Cardano.Api.Script

data ScriptLanguageInEra lang era where #

Instances

Instances details
ToJSON (ScriptLanguageInEra lang era) 
Instance details

Defined in Cardano.Api.Script

Methods

toJSON :: ScriptLanguageInEra lang era -> Value #

toEncoding :: ScriptLanguageInEra lang era -> Encoding #

toJSONList :: [ScriptLanguageInEra lang era] -> Value #

toEncodingList :: [ScriptLanguageInEra lang era] -> Encoding #

omitField :: ScriptLanguageInEra lang era -> Bool #

Show (ScriptLanguageInEra lang era) 
Instance details

Defined in Cardano.Api.Script

Eq (ScriptLanguageInEra lang era) 
Instance details

Defined in Cardano.Api.Script

Methods

(==) :: ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era -> Bool Source #

(/=) :: ScriptLanguageInEra lang era -> ScriptLanguageInEra lang era -> Bool Source #

data SimpleScript' #

Instances

Instances details
HasTypeProxy SimpleScript' 
Instance details

Defined in Cardano.Api.Script

Associated Types

data AsType SimpleScript' #

IsScriptLanguage SimpleScript' 
Instance details

Defined in Cardano.Api.Script

data AsType SimpleScript' 
Instance details

Defined in Cardano.Api.Script

data WitCtxMint #

Instances

Instances details
IsScriptWitnessInCtx WitCtxMint 
Instance details

Defined in Cardano.Api.Script

data WitCtxStake #

Instances

Instances details
IsScriptWitnessInCtx WitCtxStake 
Instance details

Defined in Cardano.Api.Script

data WitCtxTxIn #

Instances

Instances details
IsScriptWitnessInCtx WitCtxTxIn 
Instance details

Defined in Cardano.Api.Script

data HashableScriptData #

Instances

Instances details
Arbitrary HashableScriptData Source # 
Instance details

Defined in Hydra.Cardano.Api.ScriptData

FromJSON HashableScriptData Source # 
Instance details

Defined in Hydra.Cardano.Api.ScriptData

ToJSON HashableScriptData Source # 
Instance details

Defined in Hydra.Cardano.Api.ScriptData

Show HashableScriptData 
Instance details

Defined in Cardano.Api.ScriptData

HasTypeProxy HashableScriptData 
Instance details

Defined in Cardano.Api.ScriptData

Associated Types

data AsType HashableScriptData #

SerialiseAsCBOR HashableScriptData 
Instance details

Defined in Cardano.Api.ScriptData

Eq HashableScriptData 
Instance details

Defined in Cardano.Api.ScriptData

data AsType HashableScriptData 
Instance details

Defined in Cardano.Api.ScriptData

data ScriptDataJsonBytesError #

Instances

Instances details
Data ScriptDataJsonBytesError 
Instance details

Defined in Cardano.Api.ScriptData

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScriptDataJsonBytesError -> c ScriptDataJsonBytesError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScriptDataJsonBytesError Source #

toConstr :: ScriptDataJsonBytesError -> Constr Source #

dataTypeOf :: ScriptDataJsonBytesError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ScriptDataJsonBytesError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScriptDataJsonBytesError) Source #

gmapT :: (forall b. Data b => b -> b) -> ScriptDataJsonBytesError -> ScriptDataJsonBytesError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataJsonBytesError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataJsonBytesError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ScriptDataJsonBytesError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScriptDataJsonBytesError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScriptDataJsonBytesError -> m ScriptDataJsonBytesError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataJsonBytesError -> m ScriptDataJsonBytesError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataJsonBytesError -> m ScriptDataJsonBytesError Source #

Show ScriptDataJsonBytesError 
Instance details

Defined in Cardano.Api.ScriptData

Error ScriptDataJsonBytesError 
Instance details

Defined in Cardano.Api.ScriptData

data ScriptDataJsonError #

Instances

Instances details
Data ScriptDataJsonError 
Instance details

Defined in Cardano.Api.ScriptData

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScriptDataJsonError -> c ScriptDataJsonError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScriptDataJsonError Source #

toConstr :: ScriptDataJsonError -> Constr Source #

dataTypeOf :: ScriptDataJsonError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ScriptDataJsonError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScriptDataJsonError) Source #

gmapT :: (forall b. Data b => b -> b) -> ScriptDataJsonError -> ScriptDataJsonError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataJsonError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataJsonError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ScriptDataJsonError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScriptDataJsonError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScriptDataJsonError -> m ScriptDataJsonError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataJsonError -> m ScriptDataJsonError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataJsonError -> m ScriptDataJsonError Source #

Show ScriptDataJsonError 
Instance details

Defined in Cardano.Api.ScriptData

Error ScriptDataJsonError 
Instance details

Defined in Cardano.Api.ScriptData

Eq ScriptDataJsonError 
Instance details

Defined in Cardano.Api.ScriptData

data ScriptDataJsonSchemaError #

Instances

Instances details
Data ScriptDataJsonSchemaError 
Instance details

Defined in Cardano.Api.ScriptData

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScriptDataJsonSchemaError -> c ScriptDataJsonSchemaError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScriptDataJsonSchemaError Source #

toConstr :: ScriptDataJsonSchemaError -> Constr Source #

dataTypeOf :: ScriptDataJsonSchemaError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ScriptDataJsonSchemaError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScriptDataJsonSchemaError) Source #

gmapT :: (forall b. Data b => b -> b) -> ScriptDataJsonSchemaError -> ScriptDataJsonSchemaError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataJsonSchemaError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataJsonSchemaError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ScriptDataJsonSchemaError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScriptDataJsonSchemaError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScriptDataJsonSchemaError -> m ScriptDataJsonSchemaError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataJsonSchemaError -> m ScriptDataJsonSchemaError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataJsonSchemaError -> m ScriptDataJsonSchemaError Source #

Show ScriptDataJsonSchemaError 
Instance details

Defined in Cardano.Api.ScriptData

Error ScriptDataJsonSchemaError 
Instance details

Defined in Cardano.Api.ScriptData

Eq ScriptDataJsonSchemaError 
Instance details

Defined in Cardano.Api.ScriptData

newtype ScriptDataRangeError #

Instances

Instances details
Data ScriptDataRangeError 
Instance details

Defined in Cardano.Api.ScriptData

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScriptDataRangeError -> c ScriptDataRangeError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScriptDataRangeError Source #

toConstr :: ScriptDataRangeError -> Constr Source #

dataTypeOf :: ScriptDataRangeError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ScriptDataRangeError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScriptDataRangeError) Source #

gmapT :: (forall b. Data b => b -> b) -> ScriptDataRangeError -> ScriptDataRangeError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataRangeError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScriptDataRangeError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> ScriptDataRangeError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScriptDataRangeError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScriptDataRangeError -> m ScriptDataRangeError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataRangeError -> m ScriptDataRangeError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScriptDataRangeError -> m ScriptDataRangeError Source #

Show ScriptDataRangeError 
Instance details

Defined in Cardano.Api.ScriptData

Error ScriptDataRangeError 
Instance details

Defined in Cardano.Api.ScriptData

Eq ScriptDataRangeError 
Instance details

Defined in Cardano.Api.ScriptData

data Bech32DecodeError #

Instances

Instances details
Data Bech32DecodeError 
Instance details

Defined in Cardano.Api.SerialiseBech32

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bech32DecodeError -> c Bech32DecodeError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Bech32DecodeError Source #

toConstr :: Bech32DecodeError -> Constr Source #

dataTypeOf :: Bech32DecodeError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Bech32DecodeError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Bech32DecodeError) Source #

gmapT :: (forall b. Data b => b -> b) -> Bech32DecodeError -> Bech32DecodeError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bech32DecodeError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bech32DecodeError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Bech32DecodeError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Bech32DecodeError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bech32DecodeError -> m Bech32DecodeError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bech32DecodeError -> m Bech32DecodeError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bech32DecodeError -> m Bech32DecodeError Source #

Show Bech32DecodeError 
Instance details

Defined in Cardano.Api.SerialiseBech32

Error Bech32DecodeError 
Instance details

Defined in Cardano.Api.SerialiseBech32

Eq Bech32DecodeError 
Instance details

Defined in Cardano.Api.SerialiseBech32

class (HasTypeProxy a, SerialiseAsRawBytes a) => SerialiseAsBech32 a #

Minimal complete definition

bech32PrefixFor, bech32PrefixesPermitted

Instances

Instances details
SerialiseAsBech32 StakeAddress 
Instance details

Defined in Cardano.Api.Address

SerialiseAsBech32 (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

SerialiseAsBech32 (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsBech32 (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsBech32 (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsBech32 (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsBech32 (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsBech32 (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

class HasTypeProxy a => SerialiseAsCBOR a where #

Minimal complete definition

Nothing

Methods

serialiseToCBOR :: a -> ByteString #

deserialiseFromCBOR :: AsType a -> ByteString -> Either DecoderError a #

Instances

Instances details
SerialiseAsCBOR GovernancePoll 
Instance details

Defined in Cardano.Api.Governance.Poll

SerialiseAsCBOR GovernancePollAnswer 
Instance details

Defined in Cardano.Api.Governance.Poll

SerialiseAsCBOR OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

SerialiseAsCBOR OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

SerialiseAsCBOR UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

SerialiseAsCBOR HashableScriptData 
Instance details

Defined in Cardano.Api.ScriptData

SerialiseAsCBOR ScriptData 
Instance details

Defined in Cardano.Api.ScriptData

SerialiseAsCBOR TxMetadata 
Instance details

Defined in Cardano.Api.TxMetadata

IsShelleyBasedEra era => SerialiseAsCBOR (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

IsShelleyBasedEra era => SerialiseAsCBOR (Proposal era) 
Instance details

Defined in Cardano.Api.Governance.Actions.ProposalProcedure

IsShelleyBasedEra era => SerialiseAsCBOR (VotingProcedure era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

IsShelleyBasedEra era => SerialiseAsCBOR (VotingProcedures era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

SerialiseAsCBOR (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (Hash KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsCBOR (Hash VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsCBOR (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsCBOR (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsCBOR (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsCBOR (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsCBOR (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsCBOR (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsCBOR (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTypeProxy lang => SerialiseAsCBOR (PlutusScript lang) 
Instance details

Defined in Cardano.Api.Script

IsScriptLanguage lang => SerialiseAsCBOR (Script lang) 
Instance details

Defined in Cardano.Api.Script

Methods

serialiseToCBOR :: Script lang -> ByteString #

deserialiseFromCBOR :: AsType (Script lang) -> ByteString -> Either DecoderError (Script lang) #

IsCardanoEra era => SerialiseAsCBOR (KeyWitness era) 
Instance details

Defined in Cardano.Api.Tx.Sign

IsShelleyBasedEra era => SerialiseAsCBOR (Tx era) 
Instance details

Defined in Cardano.Api.Tx.Sign

Methods

serialiseToCBOR :: Tx era -> ByteString #

deserialiseFromCBOR :: AsType (Tx era) -> ByteString -> Either DecoderError (Tx era) #

IsShelleyBasedEra era => SerialiseAsCBOR (TxBody era) 
Instance details

Defined in Cardano.Api.Tx.Sign

Methods

serialiseToCBOR :: TxBody era -> ByteString #

deserialiseFromCBOR :: AsType (TxBody era) -> ByteString -> Either DecoderError (TxBody era) #

newtype JsonDecodeError #

Constructors

JsonDecodeError String 

Instances

Instances details
Data JsonDecodeError 
Instance details

Defined in Cardano.Api.SerialiseJSON

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> JsonDecodeError -> c JsonDecodeError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c JsonDecodeError Source #

toConstr :: JsonDecodeError -> Constr Source #

dataTypeOf :: JsonDecodeError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c JsonDecodeError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c JsonDecodeError) Source #

gmapT :: (forall b. Data b => b -> b) -> JsonDecodeError -> JsonDecodeError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> JsonDecodeError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> JsonDecodeError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> JsonDecodeError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> JsonDecodeError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> JsonDecodeError -> m JsonDecodeError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> JsonDecodeError -> m JsonDecodeError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> JsonDecodeError -> m JsonDecodeError Source #

Show JsonDecodeError 
Instance details

Defined in Cardano.Api.SerialiseJSON

Error JsonDecodeError 
Instance details

Defined in Cardano.Api.SerialiseJSON

Methods

prettyError :: JsonDecodeError -> Doc ann #

Eq JsonDecodeError 
Instance details

Defined in Cardano.Api.SerialiseJSON

data TextEnvelopeCddlError #

Instances

Instances details
Data TextEnvelopeCddlError 
Instance details

Defined in Cardano.Api.SerialiseLedgerCddl

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TextEnvelopeCddlError -> c TextEnvelopeCddlError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TextEnvelopeCddlError Source #

toConstr :: TextEnvelopeCddlError -> Constr Source #

dataTypeOf :: TextEnvelopeCddlError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeCddlError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextEnvelopeCddlError) Source #

gmapT :: (forall b. Data b => b -> b) -> TextEnvelopeCddlError -> TextEnvelopeCddlError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TextEnvelopeCddlError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TextEnvelopeCddlError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TextEnvelopeCddlError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TextEnvelopeCddlError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TextEnvelopeCddlError -> m TextEnvelopeCddlError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TextEnvelopeCddlError -> m TextEnvelopeCddlError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TextEnvelopeCddlError -> m TextEnvelopeCddlError Source #

Show TextEnvelopeCddlError 
Instance details

Defined in Cardano.Api.SerialiseLedgerCddl

Error TextEnvelopeCddlError 
Instance details

Defined in Cardano.Api.SerialiseLedgerCddl

Eq TextEnvelopeCddlError 
Instance details

Defined in Cardano.Api.SerialiseLedgerCddl

class (HasTypeProxy a, Typeable a) => SerialiseAsRawBytes a where #

Instances

Instances details
SerialiseAsRawBytes AddressAny 
Instance details

Defined in Cardano.Api.Address

SerialiseAsRawBytes StakeAddress 
Instance details

Defined in Cardano.Api.Address

SerialiseAsRawBytes PraosNonce 
Instance details

Defined in Cardano.Api.ProtocolParameters

SerialiseAsRawBytes ScriptHash 
Instance details

Defined in Cardano.Api.Script

SerialiseAsRawBytes TxId 
Instance details

Defined in Cardano.Api.TxIn

SerialiseAsRawBytes AssetName 
Instance details

Defined in Cardano.Api.Value

SerialiseAsRawBytes PolicyId 
Instance details

Defined in Cardano.Api.Value

SerialiseAsRawBytes (Address ByronAddr) 
Instance details

Defined in Cardano.Api.Address

SerialiseAsRawBytes (Address ShelleyAddr) 
Instance details

Defined in Cardano.Api.Address

IsCardanoEra era => SerialiseAsRawBytes (AddressInEra era) 
Instance details

Defined in Cardano.Api.Address

SerialiseAsRawBytes (Hash BlockHeader) 
Instance details

Defined in Cardano.Api.Block

SerialiseAsRawBytes (Hash DRepMetadata) 
Instance details

Defined in Cardano.Api.DRepMetadata

SerialiseAsRawBytes (Hash GovernancePoll) 
Instance details

Defined in Cardano.Api.Governance.Poll

SerialiseAsRawBytes (Hash ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (Hash ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (Hash KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsRawBytes (Hash VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsRawBytes (Hash CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (Hash ScriptData) 
Instance details

Defined in Cardano.Api.ScriptData

SerialiseAsRawBytes (Hash StakePoolMetadata) 
Instance details

Defined in Cardano.Api.StakePoolMetadata

SerialiseAsRawBytes (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsRawBytes (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsRawBytes (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

SerialiseAsRawBytes (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsRawBytes (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

SerialiseAsRawBytes (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

SerialiseAsRawBytes (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTypeProxy lang => SerialiseAsRawBytes (PlutusScript lang) 
Instance details

Defined in Cardano.Api.Script

class SerialiseAsCBOR a => HasTextEnvelope a where #

Minimal complete definition

textEnvelopeType

Instances

Instances details
HasTextEnvelope GovernancePoll 
Instance details

Defined in Cardano.Api.Governance.Poll

HasTextEnvelope OperationalCertificate 
Instance details

Defined in Cardano.Api.OperationalCertificate

HasTextEnvelope OperationalCertificateIssueCounter 
Instance details

Defined in Cardano.Api.OperationalCertificate

HasTextEnvelope UpdateProposal 
Instance details

Defined in Cardano.Api.ProtocolParameters

IsShelleyBasedEra era => HasTextEnvelope (Certificate era) 
Instance details

Defined in Cardano.Api.Certificate

IsShelleyBasedEra era => HasTextEnvelope (Proposal era) 
Instance details

Defined in Cardano.Api.Governance.Actions.ProposalProcedure

IsShelleyBasedEra era => HasTextEnvelope (VotingProcedure era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

IsShelleyBasedEra era => HasTextEnvelope (VotingProcedures era) 
Instance details

Defined in Cardano.Api.Governance.Actions.VotingProcedure

HasTextEnvelope (SigningKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

HasTextEnvelope (SigningKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

HasTextEnvelope (SigningKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

HasTextEnvelope (SigningKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

HasTextEnvelope (SigningKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (SigningKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey ByronKey) 
Instance details

Defined in Cardano.Api.Keys.Byron

HasTextEnvelope (VerificationKey ByronKeyLegacy) 
Instance details

Defined in Cardano.Api.Keys.Byron

HasTextEnvelope (VerificationKey KesKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

HasTextEnvelope (VerificationKey VrfKey) 
Instance details

Defined in Cardano.Api.Keys.Praos

HasTextEnvelope (VerificationKey CommitteeColdExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeColdKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeHotExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey CommitteeHotKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey DRepExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey DRepKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisDelegateExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisDelegateKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey GenesisUTxOKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey PaymentExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey PaymentKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey StakeExtendedKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey StakeKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

HasTextEnvelope (VerificationKey StakePoolKey) 
Instance details

Defined in Cardano.Api.Keys.Shelley

IsPlutusScriptLanguage lang => HasTextEnvelope (PlutusScript lang) 
Instance details

Defined in Cardano.Api.Script

IsScriptLanguage lang => HasTextEnvelope (Script lang) 
Instance details

Defined in Cardano.Api.Script

IsCardanoEra era => HasTextEnvelope (KeyWitness era) 
Instance details

Defined in Cardano.Api.Tx.Sign

IsShelleyBasedEra era => HasTextEnvelope (Tx era) 
Instance details

Defined in Cardano.Api.Tx.Sign

IsShelleyBasedEra era => HasTextEnvelope (TxBody era) 
Instance details

Defined in Cardano.Api.Tx.Sign

data TextEnvelopeDescr #

Instances

Instances details
FromJSON TextEnvelopeDescr 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

ToJSON TextEnvelopeDescr 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Data TextEnvelopeDescr 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TextEnvelopeDescr -> c TextEnvelopeDescr Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TextEnvelopeDescr Source #

toConstr :: TextEnvelopeDescr -> Constr Source #

dataTypeOf :: TextEnvelopeDescr -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeDescr) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextEnvelopeDescr) Source #

gmapT :: (forall b. Data b => b -> b) -> TextEnvelopeDescr -> TextEnvelopeDescr Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TextEnvelopeDescr -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TextEnvelopeDescr -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TextEnvelopeDescr -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TextEnvelopeDescr -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TextEnvelopeDescr -> m TextEnvelopeDescr Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TextEnvelopeDescr -> m TextEnvelopeDescr Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TextEnvelopeDescr -> m TextEnvelopeDescr Source #

IsString TextEnvelopeDescr 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Semigroup TextEnvelopeDescr 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Show TextEnvelopeDescr 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Eq TextEnvelopeDescr 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

data TextEnvelopeError #

Instances

Instances details
Data TextEnvelopeError 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TextEnvelopeError -> c TextEnvelopeError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TextEnvelopeError Source #

toConstr :: TextEnvelopeError -> Constr Source #

dataTypeOf :: TextEnvelopeError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextEnvelopeError) Source #

gmapT :: (forall b. Data b => b -> b) -> TextEnvelopeError -> TextEnvelopeError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TextEnvelopeError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TextEnvelopeError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TextEnvelopeError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TextEnvelopeError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TextEnvelopeError -> m TextEnvelopeError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TextEnvelopeError -> m TextEnvelopeError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TextEnvelopeError -> m TextEnvelopeError Source #

Show TextEnvelopeError 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Error TextEnvelopeError 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Eq TextEnvelopeError 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

newtype TextEnvelopeType #

Constructors

TextEnvelopeType String 

Instances

Instances details
FromJSON TextEnvelopeType 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

ToJSON TextEnvelopeType 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Data TextEnvelopeType 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TextEnvelopeType -> c TextEnvelopeType Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TextEnvelopeType Source #

toConstr :: TextEnvelopeType -> Constr Source #

dataTypeOf :: TextEnvelopeType -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TextEnvelopeType) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TextEnvelopeType) Source #

gmapT :: (forall b. Data b => b -> b) -> TextEnvelopeType -> TextEnvelopeType Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TextEnvelopeType -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TextEnvelopeType -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TextEnvelopeType -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TextEnvelopeType -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TextEnvelopeType -> m TextEnvelopeType Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TextEnvelopeType -> m TextEnvelopeType Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TextEnvelopeType -> m TextEnvelopeType Source #

IsString TextEnvelopeType 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Semigroup TextEnvelopeType 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Show TextEnvelopeType 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

Eq TextEnvelopeType 
Instance details

Defined in Cardano.Api.SerialiseTextEnvelope

newtype UsingBech32 a #

Constructors

UsingBech32 a 

Instances

Instances details
SerialiseAsBech32 a => FromJSON (UsingBech32 a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

parseJSON :: Value -> Parser (UsingBech32 a) #

parseJSONList :: Value -> Parser [UsingBech32 a] #

omittedField :: Maybe (UsingBech32 a) #

SerialiseAsBech32 a => FromJSONKey (UsingBech32 a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

fromJSONKey :: FromJSONKeyFunction (UsingBech32 a)

fromJSONKeyList :: FromJSONKeyFunction [UsingBech32 a]

SerialiseAsBech32 a => ToJSON (UsingBech32 a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

toJSON :: UsingBech32 a -> Value #

toEncoding :: UsingBech32 a -> Encoding #

toJSONList :: [UsingBech32 a] -> Value #

toEncodingList :: [UsingBech32 a] -> Encoding #

omitField :: UsingBech32 a -> Bool #

SerialiseAsBech32 a => ToJSONKey (UsingBech32 a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

toJSONKey :: ToJSONKeyFunction (UsingBech32 a)

toJSONKeyList :: ToJSONKeyFunction [UsingBech32 a]

SerialiseAsBech32 a => IsString (UsingBech32 a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

SerialiseAsBech32 a => Show (UsingBech32 a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

newtype UsingRawBytes a #

Constructors

UsingRawBytes a 

Instances

Instances details
SerialiseAsRawBytes a => FromCBOR (UsingRawBytes a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

fromCBOR :: Decoder s (UsingRawBytes a)

label :: Proxy (UsingRawBytes a) -> Text

SerialiseAsRawBytes a => ToCBOR (UsingRawBytes a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

toCBOR :: UsingRawBytes a -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (UsingRawBytes a) -> Size

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

newtype UsingRawBytesHex a #

Constructors

UsingRawBytesHex a 

Instances

Instances details
SerialiseAsRawBytes a => FromJSON (UsingRawBytesHex a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

parseJSON :: Value -> Parser (UsingRawBytesHex a) #

parseJSONList :: Value -> Parser [UsingRawBytesHex a] #

omittedField :: Maybe (UsingRawBytesHex a) #

SerialiseAsRawBytes a => FromJSONKey (UsingRawBytesHex a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

fromJSONKey :: FromJSONKeyFunction (UsingRawBytesHex a)

fromJSONKeyList :: FromJSONKeyFunction [UsingRawBytesHex a]

SerialiseAsRawBytes a => ToJSON (UsingRawBytesHex a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

toJSON :: UsingRawBytesHex a -> Value #

toEncoding :: UsingRawBytesHex a -> Encoding #

toJSONList :: [UsingRawBytesHex a] -> Value #

toEncodingList :: [UsingRawBytesHex a] -> Encoding #

omitField :: UsingRawBytesHex a -> Bool #

SerialiseAsRawBytes a => ToJSONKey (UsingRawBytesHex a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

Methods

toJSONKey :: ToJSONKeyFunction (UsingRawBytesHex a)

toJSONKeyList :: ToJSONKeyFunction [UsingRawBytesHex a]

SerialiseAsRawBytes a => IsString (UsingRawBytesHex a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

SerialiseAsRawBytes a => Show (UsingRawBytesHex a) 
Instance details

Defined in Cardano.Api.SerialiseUsing

data StakePoolMetadata #

Instances

Instances details
FromJSON StakePoolMetadata 
Instance details

Defined in Cardano.Api.StakePoolMetadata

Show StakePoolMetadata 
Instance details

Defined in Cardano.Api.StakePoolMetadata

HasTypeProxy StakePoolMetadata 
Instance details

Defined in Cardano.Api.StakePoolMetadata

Associated Types

data AsType StakePoolMetadata #

Eq StakePoolMetadata 
Instance details

Defined in Cardano.Api.StakePoolMetadata

Show (Hash StakePoolMetadata) 
Instance details

Defined in Cardano.Api.StakePoolMetadata

SerialiseAsRawBytes (Hash StakePoolMetadata) 
Instance details

Defined in Cardano.Api.StakePoolMetadata

Eq (Hash StakePoolMetadata) 
Instance details

Defined in Cardano.Api.StakePoolMetadata

data AsType StakePoolMetadata 
Instance details

Defined in Cardano.Api.StakePoolMetadata

newtype Hash StakePoolMetadata 
Instance details

Defined in Cardano.Api.StakePoolMetadata

data StakePoolMetadataValidationError #

Instances

Instances details
Data StakePoolMetadataValidationError 
Instance details

Defined in Cardano.Api.StakePoolMetadata

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> StakePoolMetadataValidationError -> c StakePoolMetadataValidationError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c StakePoolMetadataValidationError Source #

toConstr :: StakePoolMetadataValidationError -> Constr Source #

dataTypeOf :: StakePoolMetadataValidationError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c StakePoolMetadataValidationError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c StakePoolMetadataValidationError) Source #

gmapT :: (forall b. Data b => b -> b) -> StakePoolMetadataValidationError -> StakePoolMetadataValidationError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> StakePoolMetadataValidationError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> StakePoolMetadataValidationError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> StakePoolMetadataValidationError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> StakePoolMetadataValidationError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> StakePoolMetadataValidationError -> m StakePoolMetadataValidationError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> StakePoolMetadataValidationError -> m StakePoolMetadataValidationError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> StakePoolMetadataValidationError -> m StakePoolMetadataValidationError Source #

Show StakePoolMetadataValidationError 
Instance details

Defined in Cardano.Api.StakePoolMetadata

Error StakePoolMetadataValidationError 
Instance details

Defined in Cardano.Api.StakePoolMetadata

Eq StakePoolMetadataValidationError 
Instance details

Defined in Cardano.Api.StakePoolMetadata

data AnyScriptWitness era where #

Constructors

AnyScriptWitness :: forall witctx era. ScriptWitness witctx era -> AnyScriptWitness era 

Instances

Instances details
Show (AnyScriptWitness era) 
Instance details

Defined in Cardano.Api.Tx.Body

data BuildTx #

data BuildTxWith build a where #

Constructors

ViewTx :: forall a. BuildTxWith ViewTx a 
BuildTxWith :: forall a. a -> BuildTxWith BuildTx a 

Instances

Instances details
Functor (BuildTxWith build) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

fmap :: (a -> b) -> BuildTxWith build a -> BuildTxWith build b Source #

(<$) :: a -> BuildTxWith build b -> BuildTxWith build a Source #

Show a => Show (BuildTxWith build a) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

showsPrec :: Int -> BuildTxWith build a -> ShowS Source #

show :: BuildTxWith build a -> String Source #

showList :: [BuildTxWith build a] -> ShowS Source #

Eq a => Eq (BuildTxWith build a) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

(==) :: BuildTxWith build a -> BuildTxWith build a -> Bool Source #

(/=) :: BuildTxWith build a -> BuildTxWith build a -> Bool Source #

data ViewTx #

data ScriptWitnessIndex #

data TxCertificates build era where #

Constructors

TxCertificatesNone :: forall build era. TxCertificates build era 
TxCertificates :: forall era build. ShelleyBasedEra era -> [Certificate era] -> BuildTxWith build (Map StakeCredential (Witness WitCtxStake era)) -> TxCertificates build era 

Instances

Instances details
Show (TxCertificates build era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

showsPrec :: Int -> TxCertificates build era -> ShowS Source #

show :: TxCertificates build era -> String Source #

showList :: [TxCertificates build era] -> ShowS Source #

Eq (TxCertificates build era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

(==) :: TxCertificates build era -> TxCertificates build era -> Bool Source #

(/=) :: TxCertificates build era -> TxCertificates build era -> Bool Source #

data TxOutInAnyEra where #

Constructors

TxOutInAnyEra :: forall era. CardanoEra era -> TxOut CtxTx era -> TxOutInAnyEra 

Instances

Instances details
Show TxOutInAnyEra 
Instance details

Defined in Cardano.Api.Tx.Body

Eq TxOutInAnyEra 
Instance details

Defined in Cardano.Api.Tx.Body

Pretty TxOutInAnyEra 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

pretty :: TxOutInAnyEra -> Doc ann #

prettyList :: [TxOutInAnyEra] -> Doc ann #

data TxProposalProcedures build era where #

Constructors

TxProposalProceduresNone :: forall build era. TxProposalProcedures build era 
TxProposalProcedures :: forall era build. EraPParams (ShelleyLedgerEra era) => OSet (ProposalProcedure (ShelleyLedgerEra era)) -> BuildTxWith build (Map (ProposalProcedure (ShelleyLedgerEra era)) (ScriptWitness WitCtxStake era)) -> TxProposalProcedures build era 

Instances

Instances details
Show (TxProposalProcedures build era) 
Instance details

Defined in Cardano.Api.Tx.Body

Eq (TxProposalProcedures build era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

(==) :: TxProposalProcedures build era -> TxProposalProcedures build era -> Bool Source #

(/=) :: TxProposalProcedures build era -> TxProposalProcedures build era -> Bool Source #

data TxReturnCollateral ctx era where #

Constructors

TxReturnCollateralNone :: forall ctx era. TxReturnCollateral ctx era 
TxReturnCollateral :: forall era ctx. BabbageEraOnwards era -> TxOut ctx era -> TxReturnCollateral ctx era 

Instances

Instances details
Show (TxReturnCollateral ctx era) 
Instance details

Defined in Cardano.Api.Tx.Body

Eq (TxReturnCollateral ctx era) 
Instance details

Defined in Cardano.Api.Tx.Body

data TxTotalCollateral era where #

Constructors

TxTotalCollateralNone :: forall era. TxTotalCollateral era 
TxTotalCollateral :: forall era. BabbageEraOnwards era -> Coin -> TxTotalCollateral era 

Instances

Instances details
Show (TxTotalCollateral era) 
Instance details

Defined in Cardano.Api.Tx.Body

Eq (TxTotalCollateral era) 
Instance details

Defined in Cardano.Api.Tx.Body

data TxUpdateProposal era where #

Constructors

TxUpdateProposalNone :: forall era. TxUpdateProposal era 
TxUpdateProposal :: forall era. ShelleyToBabbageEra era -> UpdateProposal -> TxUpdateProposal era 

Instances

Instances details
Show (TxUpdateProposal era) 
Instance details

Defined in Cardano.Api.Tx.Body

Eq (TxUpdateProposal era) 
Instance details

Defined in Cardano.Api.Tx.Body

data TxVotingProcedures build era where #

Constructors

TxVotingProceduresNone :: forall build era. TxVotingProcedures build era 
TxVotingProcedures :: forall era build. VotingProcedures (ShelleyLedgerEra era) -> BuildTxWith build (Map (Voter (EraCrypto (ShelleyLedgerEra era))) (ScriptWitness WitCtxStake era)) -> TxVotingProcedures build era 

Instances

Instances details
Show (TxVotingProcedures build era) 
Instance details

Defined in Cardano.Api.Tx.Body

Eq (TxVotingProcedures build era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

(==) :: TxVotingProcedures build era -> TxVotingProcedures build era -> Bool Source #

(/=) :: TxVotingProcedures build era -> TxVotingProcedures build era -> Bool Source #

data TxWithdrawals build era where #

Constructors

TxWithdrawalsNone :: forall build era. TxWithdrawals build era 
TxWithdrawals :: forall era build. ShelleyBasedEra era -> [(StakeAddress, Coin, BuildTxWith build (Witness WitCtxStake era))] -> TxWithdrawals build era 

Instances

Instances details
Show (TxWithdrawals build era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

showsPrec :: Int -> TxWithdrawals build era -> ShowS Source #

show :: TxWithdrawals build era -> String Source #

showList :: [TxWithdrawals build era] -> ShowS Source #

Eq (TxWithdrawals build era) 
Instance details

Defined in Cardano.Api.Tx.Body

Methods

(==) :: TxWithdrawals build era -> TxWithdrawals build era -> Bool Source #

(/=) :: TxWithdrawals build era -> TxWithdrawals build era -> Bool Source #

data ScriptValidity #

Constructors

ScriptInvalid 
ScriptValid 

Instances

Instances details
Show ScriptValidity 
Instance details

Defined in Cardano.Api.Tx.Sign

DecCBOR ScriptValidity 
Instance details

Defined in Cardano.Api.Tx.Sign

Methods

decCBOR :: Decoder s ScriptValidity

dropCBOR :: Proxy ScriptValidity -> Decoder s ()

label :: Proxy ScriptValidity -> Text

EncCBOR ScriptValidity 
Instance details

Defined in Cardano.Api.Tx.Sign

Methods

encCBOR :: ScriptValidity -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy ScriptValidity -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ScriptValidity] -> Size

Eq ScriptValidity 
Instance details

Defined in Cardano.Api.Tx.Sign

newtype TxIx #

Constructors

TxIx Word 

Instances

Instances details
FromJSON TxIx 
Instance details

Defined in Cardano.Api.TxIn

Methods

parseJSON :: Value -> Parser TxIx #

parseJSONList :: Value -> Parser [TxIx] #

omittedField :: Maybe TxIx #

ToJSON TxIx 
Instance details

Defined in Cardano.Api.TxIn

Methods

toJSON :: TxIx -> Value #

toEncoding :: TxIx -> Encoding #

toJSONList :: [TxIx] -> Value #

toEncodingList :: [TxIx] -> Encoding #

omitField :: TxIx -> Bool #

Enum TxIx 
Instance details

Defined in Cardano.Api.TxIn

Show TxIx 
Instance details

Defined in Cardano.Api.TxIn

Eq TxIx 
Instance details

Defined in Cardano.Api.TxIn

Methods

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

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

Ord TxIx 
Instance details

Defined in Cardano.Api.TxIn

data TxMetadataJsonError #

Instances

Instances details
Data TxMetadataJsonError 
Instance details

Defined in Cardano.Api.TxMetadata

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TxMetadataJsonError -> c TxMetadataJsonError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TxMetadataJsonError Source #

toConstr :: TxMetadataJsonError -> Constr Source #

dataTypeOf :: TxMetadataJsonError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TxMetadataJsonError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TxMetadataJsonError) Source #

gmapT :: (forall b. Data b => b -> b) -> TxMetadataJsonError -> TxMetadataJsonError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TxMetadataJsonError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TxMetadataJsonError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TxMetadataJsonError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TxMetadataJsonError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TxMetadataJsonError -> m TxMetadataJsonError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TxMetadataJsonError -> m TxMetadataJsonError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TxMetadataJsonError -> m TxMetadataJsonError Source #

Show TxMetadataJsonError 
Instance details

Defined in Cardano.Api.TxMetadata

Error TxMetadataJsonError 
Instance details

Defined in Cardano.Api.TxMetadata

Eq TxMetadataJsonError 
Instance details

Defined in Cardano.Api.TxMetadata

data TxMetadataJsonSchemaError #

Instances

Instances details
Data TxMetadataJsonSchemaError 
Instance details

Defined in Cardano.Api.TxMetadata

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TxMetadataJsonSchemaError -> c TxMetadataJsonSchemaError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TxMetadataJsonSchemaError Source #

toConstr :: TxMetadataJsonSchemaError -> Constr Source #

dataTypeOf :: TxMetadataJsonSchemaError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TxMetadataJsonSchemaError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TxMetadataJsonSchemaError) Source #

gmapT :: (forall b. Data b => b -> b) -> TxMetadataJsonSchemaError -> TxMetadataJsonSchemaError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TxMetadataJsonSchemaError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TxMetadataJsonSchemaError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TxMetadataJsonSchemaError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TxMetadataJsonSchemaError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TxMetadataJsonSchemaError -> m TxMetadataJsonSchemaError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TxMetadataJsonSchemaError -> m TxMetadataJsonSchemaError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TxMetadataJsonSchemaError -> m TxMetadataJsonSchemaError Source #

Show TxMetadataJsonSchemaError 
Instance details

Defined in Cardano.Api.TxMetadata

Error TxMetadataJsonSchemaError 
Instance details

Defined in Cardano.Api.TxMetadata

Eq TxMetadataJsonSchemaError 
Instance details

Defined in Cardano.Api.TxMetadata

data TxMetadataRangeError #

Instances

Instances details
Data TxMetadataRangeError 
Instance details

Defined in Cardano.Api.TxMetadata

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TxMetadataRangeError -> c TxMetadataRangeError Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TxMetadataRangeError Source #

toConstr :: TxMetadataRangeError -> Constr Source #

dataTypeOf :: TxMetadataRangeError -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TxMetadataRangeError) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TxMetadataRangeError) Source #

gmapT :: (forall b. Data b => b -> b) -> TxMetadataRangeError -> TxMetadataRangeError Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TxMetadataRangeError -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TxMetadataRangeError -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> TxMetadataRangeError -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TxMetadataRangeError -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TxMetadataRangeError -> m TxMetadataRangeError Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TxMetadataRangeError -> m TxMetadataRangeError Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TxMetadataRangeError -> m TxMetadataRangeError Source #

Show TxMetadataRangeError 
Instance details

Defined in Cardano.Api.TxMetadata

Error TxMetadataRangeError 
Instance details

Defined in Cardano.Api.TxMetadata

Eq TxMetadataRangeError 
Instance details

Defined in Cardano.Api.TxMetadata

data AssetId #

Instances

Instances details
Show AssetId 
Instance details

Defined in Cardano.Api.Value

Eq AssetId 
Instance details

Defined in Cardano.Api.Value

Ord AssetId 
Instance details

Defined in Cardano.Api.Value

newtype AssetName #

Constructors

AssetName ByteString 

Instances

Instances details
FromJSON AssetName 
Instance details

Defined in Cardano.Api.Value

Methods

parseJSON :: Value -> Parser AssetName #

parseJSONList :: Value -> Parser [AssetName] #

omittedField :: Maybe AssetName #

FromJSONKey AssetName 
Instance details

Defined in Cardano.Api.Value

Methods

fromJSONKey :: FromJSONKeyFunction AssetName

fromJSONKeyList :: FromJSONKeyFunction [AssetName]

ToJSON AssetName 
Instance details

Defined in Cardano.Api.Value

Methods

toJSON :: AssetName -> Value #

toEncoding :: AssetName -> Encoding #

toJSONList :: [AssetName] -> Value #

toEncodingList :: [AssetName] -> Encoding #

omitField :: AssetName -> Bool #

ToJSONKey AssetName 
Instance details

Defined in Cardano.Api.Value

Methods

toJSONKey :: ToJSONKeyFunction AssetName

toJSONKeyList :: ToJSONKeyFunction [AssetName]

IsString AssetName 
Instance details

Defined in Cardano.Api.Value

Show AssetName 
Instance details

Defined in Cardano.Api.Value

HasTypeProxy AssetName 
Instance details

Defined in Cardano.Api.Value

Associated Types

data AsType AssetName #

SerialiseAsRawBytes AssetName 
Instance details

Defined in Cardano.Api.Value

Eq AssetName 
Instance details

Defined in Cardano.Api.Value

Ord AssetName 
Instance details

Defined in Cardano.Api.Value

data AsType AssetName 
Instance details

Defined in Cardano.Api.Value

newtype Quantity #

Constructors

Quantity Integer 

Instances

Instances details
FromJSON Quantity 
Instance details

Defined in Cardano.Api.Value

Methods

parseJSON :: Value -> Parser Quantity #

parseJSONList :: Value -> Parser [Quantity] #

omittedField :: Maybe Quantity #

ToJSON Quantity 
Instance details

Defined in Cardano.Api.Value

Methods

toJSON :: Quantity -> Value #

toEncoding :: Quantity -> Encoding #

toJSONList :: [Quantity] -> Value #

toEncodingList :: [Quantity] -> Encoding #

omitField :: Quantity -> Bool #

Data Quantity 
Instance details

Defined in Cardano.Api.Value

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Quantity -> c Quantity Source #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Quantity Source #

toConstr :: Quantity -> Constr Source #

dataTypeOf :: Quantity -> DataType Source #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Quantity) Source #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Quantity) Source #

gmapT :: (forall b. Data b => b -> b) -> Quantity -> Quantity Source #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Quantity -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Quantity -> r Source #

gmapQ :: (forall d. Data d => d -> u) -> Quantity -> [u] Source #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Quantity -> u Source #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Quantity -> m Quantity Source #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Quantity -> m Quantity Source #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Quantity -> m Quantity Source #

Monoid Quantity 
Instance details

Defined in Cardano.Api.Value

Semigroup Quantity 
Instance details

Defined in Cardano.Api.Value

Num Quantity 
Instance details

Defined in Cardano.Api.Value

Show Quantity 
Instance details

Defined in Cardano.Api.Value

Eq Quantity 
Instance details

Defined in Cardano.Api.Value

Ord Quantity 
Instance details

Defined in Cardano.Api.Value

newtype ShowOf a #

Constructors

ShowOf a 

Instances

Instances details
Show a => ToJSON (ShowOf a) 
Instance details

Defined in Cardano.Api.Via.ShowOf

Methods

toJSON :: ShowOf a -> Value #

toEncoding :: ShowOf a -> Encoding #

toJSONList :: [ShowOf a] -> Value #

toEncodingList :: [ShowOf a] -> Encoding #

omitField :: ShowOf a -> Bool #

Show a => ToJSONKey (ShowOf a) 
Instance details

Defined in Cardano.Api.Via.ShowOf

Methods

toJSONKey :: ToJSONKeyFunction (ShowOf a)

toJSONKeyList :: ToJSONKeyFunction [ShowOf a]

Show a => Show (ShowOf a) 
Instance details

Defined in Cardano.Api.Via.ShowOf

Show a => Pretty (ShowOf a) 
Instance details

Defined in Cardano.Api.Via.ShowOf

Methods

pretty :: ShowOf a -> Doc ann #

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

data CommitteeMembersState c #

Constructors

CommitteeMembersState 

Fields

Instances

Instances details
Crypto c => ToJSON (CommitteeMembersState c) 
Instance details

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

Generic (CommitteeMembersState c) 
Instance details

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

Associated Types

type Rep (CommitteeMembersState c) :: Type -> Type Source #

Show (CommitteeMembersState c) 
Instance details

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

Crypto c => DecCBOR (CommitteeMembersState c) 
Instance details

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

Crypto c => EncCBOR (CommitteeMembersState c) 
Instance details

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

Methods

encCBOR :: CommitteeMembersState c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (CommitteeMembersState c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [CommitteeMembersState c] -> Size

Eq (CommitteeMembersState c) 
Instance details

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

Ord (CommitteeMembersState c) 
Instance details

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

type Rep (CommitteeMembersState c) 
Instance details

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

type Rep (CommitteeMembersState c) = D1 ('MetaData "CommitteeMembersState" "Cardano.Ledger.Api.State.Query.CommitteeMembersState" "cardano-ledger-api-1.8.0.0-6AKS8QRbXTqKkwtcAnwZoS" 'False) (C1 ('MetaCons "CommitteeMembersState" 'PrefixI 'True) (S1 ('MetaSel ('Just "csCommittee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'ColdCommitteeRole c) (CommitteeMemberState c))) :*: (S1 ('MetaSel ('Just "csQuorum") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 UnitInterval) :*: S1 ('MetaSel ('Just "csEpochNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo))))

data MemberStatus #

Constructors

Active 
Expired 
Unrecognized 

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 :: Type -> Type Source #

Show MemberStatus 
Instance details

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

DecCBOR MemberStatus 
Instance details

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

Methods

decCBOR :: Decoder s MemberStatus

dropCBOR :: Proxy MemberStatus -> Decoder s ()

label :: Proxy MemberStatus -> Text

EncCBOR MemberStatus 
Instance details

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

Methods

encCBOR :: MemberStatus -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy MemberStatus -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [MemberStatus] -> Size

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.8.0.0-6AKS8QRbXTqKkwtcAnwZoS" '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)))

newtype EpochSlots #

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 :: Type -> Type Source #

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

Methods

fromCBOR :: Decoder s EpochSlots

label :: Proxy EpochSlots -> Text

ToCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Methods

toCBOR :: EpochSlots -> Encoding

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

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

DecCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Methods

decCBOR :: Decoder s EpochSlots

dropCBOR :: Proxy EpochSlots -> Decoder s ()

label :: Proxy EpochSlots -> Text

EncCBOR EpochSlots 
Instance details

Defined in Cardano.Chain.Slotting.EpochSlots

Methods

encCBOR :: EpochSlots -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy EpochSlots -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [EpochSlots] -> Size

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.0.0.4-FNiR9cQzIruHqkKMDIYFtZ" 'True) (C1 ('MetaCons "EpochSlots" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochSlots") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

data MIRPot #

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 :: Type -> Type Source #

Show MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

DecCBOR MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

decCBOR :: Decoder s MIRPot

dropCBOR :: Proxy MIRPot -> Decoder s ()

label :: Proxy MIRPot -> Text

EncCBOR MIRPot 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

encCBOR :: MIRPot -> Encoding

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

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

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.9.0.0-7HgzAx4k96DEHFChwYPQhk" 'False) (C1 ('MetaCons "ReservesMIR" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "TreasuryMIR" 'PrefixI 'False) (U1 :: Type -> Type))

data MIRTarget c #

Constructors

StakeAddressesMIR !(Map (Credential 'Staking c) DeltaCoin) 
SendToOppositePotMIR !Coin 

Instances

Instances details
Crypto c => ToJSON (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

toJSON :: MIRTarget c -> Value #

toEncoding :: MIRTarget c -> Encoding #

toJSONList :: [MIRTarget c] -> Value #

toEncodingList :: [MIRTarget c] -> Encoding #

omitField :: MIRTarget c -> Bool #

Generic (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep (MIRTarget c) :: Type -> Type Source #

Methods

from :: MIRTarget c -> Rep (MIRTarget c) x Source #

to :: Rep (MIRTarget c) x -> MIRTarget c Source #

Show (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Crypto c => DecCBOR (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

decCBOR :: Decoder s (MIRTarget c)

dropCBOR :: Proxy (MIRTarget c) -> Decoder s ()

label :: Proxy (MIRTarget c) -> Text

Crypto c => EncCBOR (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

encCBOR :: MIRTarget c -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (MIRTarget c) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [MIRTarget c] -> Size

NFData (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnf :: MIRTarget c -> () Source #

Eq (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

NoThunks (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

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

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

showTypeOf :: Proxy (MIRTarget c) -> String

type Rep (MIRTarget c) 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep (MIRTarget c) = D1 ('MetaData "MIRTarget" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.9.0.0-7HgzAx4k96DEHFChwYPQhk" 'False) (C1 ('MetaCons "StakeAddressesMIR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'Staking c) DeltaCoin))) :+: C1 ('MetaCons "SendToOppositePotMIR" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin)))

newtype BlockNo #

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 :: Type -> Type Source #

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

Methods

fromCBOR :: Decoder s BlockNo

label :: Proxy BlockNo -> Text

ToCBOR BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

toCBOR :: BlockNo -> Encoding

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

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

DecCBOR BlockNo 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.DecCBOR

Methods

decCBOR :: Decoder s BlockNo

dropCBOR :: Proxy BlockNo -> Decoder s ()

label :: Proxy BlockNo -> Text

EncCBOR BlockNo 
Instance details

Defined in Cardano.Ledger.Binary.Encoding.EncCBOR

Methods

encCBOR :: BlockNo -> Encoding

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

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [BlockNo] -> Size

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

Serialise BlockNo 
Instance details

Defined in Cardano.Slotting.Block

Methods

encode :: BlockNo -> Encoding

decode :: Decoder s BlockNo

encodeList :: [BlockNo] -> Encoding

decodeList :: Decoder s [BlockNo]

type Rep BlockNo 
Instance details

Defined in Cardano.Slotting.Block

type Rep BlockNo = D1 ('MetaData "BlockNo" "Cardano.Slotting.Block" "cardano-slotting-0.1.2.0-6BuG7gNejVDGbM1vDRJNbs" 'True) (C1 ('MetaCons "BlockNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBlockNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

newtype EpochNo #

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 :: Type -> Type Source #

Num EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Show EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

FromCBOR EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

fromCBOR :: Decoder s EpochNo

label :: Proxy EpochNo -> Text

ToCBOR EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: EpochNo -> Encoding

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

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

DecCBOR EpochNo 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.DecCBOR

Methods

decCBOR :: Decoder s EpochNo

dropCBOR :: Proxy EpochNo -> Decoder s ()

label :: Proxy EpochNo -> Text

EncCBOR EpochNo 
Instance details

Defined in Cardano.Ledger.Binary.Encoding.EncCBOR

Methods

encCBOR :: EpochNo -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy EpochNo -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [EpochNo] -> Size

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

Serialise EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

encode :: EpochNo -> Encoding

decode :: Decoder s EpochNo

encodeList :: [EpochNo] -> Encoding

decodeList :: Decoder s [EpochNo]

type Rep EpochNo 
Instance details

Defined in Cardano.Slotting.Slot

type Rep EpochNo = D1 ('MetaData "EpochNo" "Cardano.Slotting.Slot" "cardano-slotting-0.1.2.0-6BuG7gNejVDGbM1vDRJNbs" 'True) (C1 ('MetaCons "EpochNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unEpochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

newtype SlotNo #

Constructors

SlotNo 

Fields

Instances

Instances details
FromJSON SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

parseJSON :: Value -> Parser SlotNo #

parseJSONList :: Value -> Parser [SlotNo] #

omittedField :: Maybe SlotNo #

ToJSON SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toJSON :: SlotNo -> Value #

toEncoding :: SlotNo -> Encoding #

toJSONList :: [SlotNo] -> Value #

toEncodingList :: [SlotNo] -> Encoding #

omitField :: SlotNo -> Bool #

Bounded SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Enum SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Generic SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Associated Types

type Rep SlotNo :: Type -> Type Source #

Num SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Show SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

FromCBOR SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

fromCBOR :: Decoder s SlotNo

label :: Proxy SlotNo -> Text

ToCBOR SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

toCBOR :: SlotNo -> Encoding

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

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

DecCBOR SlotNo 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.DecCBOR

Methods

decCBOR :: Decoder s SlotNo

dropCBOR :: Proxy SlotNo -> Decoder s ()

label :: Proxy SlotNo -> Text

EncCBOR SlotNo 
Instance details

Defined in Cardano.Ledger.Binary.Encoding.EncCBOR

Methods

encCBOR :: SlotNo -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy SlotNo -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [SlotNo] -> Size

NFData SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

rnf :: SlotNo -> () Source #

Eq SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Ord SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

NoThunks SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

noThunks :: Context -> SlotNo -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> SlotNo -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy SlotNo -> String

Serialise SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

Methods

encode :: SlotNo -> Encoding

decode :: Decoder s SlotNo

encodeList :: [SlotNo] -> Encoding

decodeList :: Decoder s [SlotNo]

type Rep SlotNo 
Instance details

Defined in Cardano.Slotting.Slot

type Rep SlotNo = D1 ('MetaData "SlotNo" "Cardano.Slotting.Slot" "cardano-slotting-0.1.2.0-6BuG7gNejVDGbM1vDRJNbs" 'True) (C1 ('MetaCons "SlotNo" 'PrefixI 'True) (S1 ('MetaSel ('Just "unSlotNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word64)))

newtype SystemStart #

Constructors

SystemStart 

Instances

Instances details
FromJSON SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

parseJSON :: Value -> Parser SystemStart #

parseJSONList :: Value -> Parser [SystemStart] #

omittedField :: Maybe SystemStart #

ToJSON SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

toJSON :: SystemStart -> Value #

toEncoding :: SystemStart -> Encoding #

toJSONList :: [SystemStart] -> Value #

toEncodingList :: [SystemStart] -> Encoding #

omitField :: SystemStart -> Bool #

Generic SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Associated Types

type Rep SystemStart :: Type -> Type Source #

Show SystemStart 
Instance details

Defined in Cardano.Slotting.Time

FromCBOR SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

fromCBOR :: Decoder s SystemStart

label :: Proxy SystemStart -> Text

ToCBOR SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

toCBOR :: SystemStart -> Encoding

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

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

DecCBOR SystemStart 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.DecCBOR

Methods

decCBOR :: Decoder s SystemStart

dropCBOR :: Proxy SystemStart -> Decoder s ()

label :: Proxy SystemStart -> Text

EncCBOR SystemStart 
Instance details

Defined in Cardano.Ledger.Binary.Encoding.EncCBOR

Methods

encCBOR :: SystemStart -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy SystemStart -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [SystemStart] -> Size

Eq SystemStart 
Instance details

Defined in Cardano.Slotting.Time

NoThunks SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

noThunks :: Context -> SystemStart -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> SystemStart -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy SystemStart -> String

Serialise SystemStart 
Instance details

Defined in Cardano.Slotting.Time

Methods

encode :: SystemStart -> Encoding

decode :: Decoder s SystemStart

encodeList :: [SystemStart] -> Encoding

decodeList :: Decoder s [SystemStart]

type Rep SystemStart 
Instance details

Defined in Cardano.Slotting.Time

type Rep SystemStart = D1 ('MetaData "SystemStart" "Cardano.Slotting.Time" "cardano-slotting-0.1.2.0-6BuG7gNejVDGbM1vDRJNbs" 'True) (C1 ('MetaCons "SystemStart" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSystemStart") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UTCTime)))

newtype NetworkMagic #

Constructors

NetworkMagic 

Instances

Instances details
Generic NetworkMagic 
Instance details

Defined in Ouroboros.Network.Magic

Associated Types

type Rep NetworkMagic :: Type -> Type Source #

Show NetworkMagic 
Instance details

Defined in Ouroboros.Network.Magic

Eq NetworkMagic 
Instance details

Defined in Ouroboros.Network.Magic

NoThunks NetworkMagic 
Instance details

Defined in Ouroboros.Network.Magic

Methods

noThunks :: Context -> NetworkMagic -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> NetworkMagic -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy NetworkMagic -> String

type Rep NetworkMagic 
Instance details

Defined in Ouroboros.Network.Magic

type Rep NetworkMagic = D1 ('MetaData "NetworkMagic" "Ouroboros.Network.Magic" "ouroboros-network-api-0.7.1.0-LHMsiwkd0TIG0v8t5RG281" 'True) (C1 ('MetaCons "NetworkMagic" 'PrefixI 'True) (S1 ('MetaSel ('Just "unNetworkMagic") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

data NodeToClientVersion #

Instances

Instances details
Bounded NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

Enum NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

Generic NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

Associated Types

type Rep NodeToClientVersion :: Type -> Type Source #

Show NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

NFData NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

Eq NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

Ord NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

MonadReader NodeToClientVersion (LocalStateQueryExpr block point query r m) 
Instance details

Defined in Cardano.Api.IPC.Monad

Methods

ask :: LocalStateQueryExpr block point query r m NodeToClientVersion Source #

local :: (NodeToClientVersion -> NodeToClientVersion) -> LocalStateQueryExpr block point query r m a -> LocalStateQueryExpr block point query r m a Source #

reader :: (NodeToClientVersion -> a) -> LocalStateQueryExpr block point query r m a Source #

type Rep NodeToClientVersion 
Instance details

Defined in Ouroboros.Network.NodeToClient.Version

type Rep NodeToClientVersion = D1 ('MetaData "NodeToClientVersion" "Ouroboros.Network.NodeToClient.Version" "ouroboros-network-api-0.7.1.0-LHMsiwkd0TIG0v8t5RG281" 'False) (((C1 ('MetaCons "NodeToClientV_9" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NodeToClientV_10" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NodeToClientV_11" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NodeToClientV_12" 'PrefixI 'False) (U1 :: Type -> Type))) :+: ((C1 ('MetaCons "NodeToClientV_13" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NodeToClientV_14" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "NodeToClientV_15" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NodeToClientV_16" 'PrefixI 'False) (U1 :: Type -> Type))))

newtype ChainSyncClient header point tip (m :: Type -> Type) a #

Constructors

ChainSyncClient 

Fields

newtype ChainSyncClientPipelined header point tip (m :: Type -> Type) a #

Constructors

ChainSyncClientPipelined 

Fields

newtype LocalStateQueryClient block point (query :: Type -> Type) (m :: Type -> Type) a #

Constructors

LocalStateQueryClient 

Fields

newtype LocalTxMonitorClient txid tx slot (m :: Type -> Type) a #

Constructors

LocalTxMonitorClient 

Fields

data MempoolSizeAndCapacity #

Instances

Instances details
Generic MempoolSizeAndCapacity 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

Associated Types

type Rep MempoolSizeAndCapacity :: Type -> Type Source #

Show MempoolSizeAndCapacity 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

NFData MempoolSizeAndCapacity 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

Eq MempoolSizeAndCapacity 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

type Rep MempoolSizeAndCapacity 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxMonitor.Type

type Rep MempoolSizeAndCapacity = D1 ('MetaData "MempoolSizeAndCapacity" "Ouroboros.Network.Protocol.LocalTxMonitor.Type" "ouroboros-network-protocols-0.8.1.0-DsmwONh1CNcFkOeOcrrFjR" 'False) (C1 ('MetaCons "MempoolSizeAndCapacity" 'PrefixI 'True) (S1 ('MetaSel ('Just "capacityInBytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32) :*: (S1 ('MetaSel ('Just "sizeInBytes") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32) :*: S1 ('MetaSel ('Just "numberOfTxs") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word32))))

newtype LocalTxSubmissionClient tx reject (m :: Type -> Type) a #

Constructors

LocalTxSubmissionClient 

Fields

data SubmitResult reason #

Constructors

SubmitSuccess 
SubmitFail reason 

Instances

Instances details
Functor SubmitResult 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxSubmission.Type

Methods

fmap :: (a -> b) -> SubmitResult a -> SubmitResult b Source #

(<$) :: a -> SubmitResult b -> SubmitResult a Source #

Eq reason => Eq (SubmitResult reason) 
Instance details

Defined in Ouroboros.Network.Protocol.LocalTxSubmission.Type

Methods

(==) :: SubmitResult reason -> SubmitResult reason -> Bool Source #

(/=) :: SubmitResult reason -> SubmitResult reason -> Bool Source #

pattern Block :: BlockHeader -> [Tx era] -> Block era #

runParsecParser :: Parser a -> Text -> Parser a #

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 #

throwE :: forall (m :: Type -> Type) e a. Monad m => e -> ExceptT e m a Source #

Signal an exception value e.

hsep :: [Doc ann] -> Doc ann #

runExcept :: Except e a -> Either e a Source #

Extractor for computations in the exception monad. (The inverse of except).

mapExcept :: (Either e a -> Either e' b) -> Except e a -> Except e' b Source #

Map the unwrapped computation using the given function.

withExcept :: (e -> e') -> Except e a -> Except e' a Source #

Transform any exceptions thrown by the computation using the given function (a specialization of withExceptT).

runExceptT :: ExceptT e m a -> m (Either e a) Source #

The inverse of ExceptT.

mapExceptT :: (m (Either e a) -> n (Either e' b)) -> ExceptT e m a -> ExceptT e' n b Source #

Map the unwrapped computation using the given function.

withExceptT :: forall (m :: Type -> Type) e e' a. Functor m => (e -> e') -> ExceptT e m a -> ExceptT e' m a Source #

Transform any exceptions thrown by the computation using the given function.

liftCallCC :: CallCC m (Either e a) (Either e b) -> CallCC (ExceptT e m) a b Source #

Lift a callCC operation to the new monad.

liftEither :: MonadError e m => Either e a -> m a Source #

Lifts an Either e into any MonadError e.

do { val <- liftEither =<< action1; action2 }

where action1 returns an Either to represent errors.

Since: mtl-2.2.2

modifyError :: forall e' t (m :: Type -> Type) e a. MonadTransError e' t m => (e -> e') -> ExceptT e m a -> t m a #

catchE Source #

Arguments

:: forall (m :: Type -> Type) e a e'. Monad m 
=> ExceptT e m a

the inner computation

-> (e -> ExceptT e' m a)

a handler for exceptions in the inner computation

-> ExceptT e' m a 

Handle an exception.

except :: forall (m :: Type -> Type) e a. Monad m => Either e a -> ExceptT e m a Source #

Constructor for computations in the exception monad. (The inverse of runExcept).

handleE :: forall (m :: Type -> Type) e e' a. Monad m => (e -> ExceptT e' m a) -> ExceptT e m a -> ExceptT e' m a Source #

The same as flip catchE, which is useful in situations where the code for the handler is shorter.

tryE :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> ExceptT e m (Either e a) Source #

Similar to catchE, but returns an Either result which is (Right a) if no exception was thown, or (Left ex) if an exception ex was thrown.

finallyE :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> ExceptT e m () -> ExceptT e m a Source #

finallyE a b executes computation a followed by computation b, even if a exits early by throwing an exception. In the latter case, the exception is re-thrown after b has been executed.

liftListen :: Monad m => Listen w m (Either e a) -> Listen w (ExceptT e m) a Source #

Lift a listen operation to the new monad.

liftPass :: Monad m => Pass w m (Either e a) -> Pass w (ExceptT e m) a Source #

Lift a pass operation to the new monad.

hoistMaybe :: forall (m :: Type -> Type) x a. Monad m => x -> Maybe a -> ExceptT x m a #

mapSomeAddressVerificationKey :: (forall keyrole. Key keyrole => VerificationKey keyrole -> a) -> SomeAddressVerificationKey -> a #

alonzoEraOnwardsConstraints :: AlonzoEraOnwards era -> (AlonzoEraOnwardsConstraints era => a) -> a #

babbageEraOnwardsConstraints :: BabbageEraOnwards era -> (BabbageEraOnwardsConstraints era => a) -> a #

byronToAlonzoEraConstraints :: ByronToAlonzoEra era -> (ByronToAlonzoEraConstraints era => a) -> a #

conwayEraOnwardsConstraints :: ConwayEraOnwards era -> (ConwayEraOnwardsConstraints era => a) -> a #

maryEraOnwardsConstraints :: MaryEraOnwards era -> (MaryEraOnwardsConstraints era => a) -> a #

forShelleyBasedEraInEon :: Eon eon => ShelleyBasedEra era -> a -> (eon era -> a) -> a #

forShelleyBasedEraInEonMaybe :: Eon eon => ShelleyBasedEra era -> (eon era -> a) -> Maybe a #

inEonForShelleyBasedEra :: Eon eon => a -> (eon era -> a) -> ShelleyBasedEra era -> a #

inEonForShelleyBasedEraMaybe :: Eon eon => (eon era -> a) -> ShelleyBasedEra era -> Maybe a #

shelleyBasedEraConstraints :: ShelleyBasedEra era -> (ShelleyBasedEraConstraints era => a) -> a #

shelleyEraOnlyConstraints :: ShelleyEraOnly era -> (ShelleyEraOnlyConstraints era => a) -> a #

shelleyToAllegraEraConstraints :: ShelleyToAllegraEra era -> (ShelleyToAllegraEraConstraints era => a) -> a #

shelleyToAlonzoEraConstraints :: ShelleyToAlonzoEra era -> (ShelleyToAlonzoEraConstraints era => a) -> a #

shelleyToBabbageEraConstraints :: ShelleyToBabbageEra era -> (ShelleyToBabbageEraConstraints era => a) -> a #

shelleyToMaryEraConstraints :: ShelleyToMaryEra era -> (ShelleyToMaryEraConstraints era => a) -> a #

caseByronOrShelleyBasedEra :: a -> (ShelleyBasedEraConstraints era => ShelleyBasedEra era -> a) -> CardanoEra era -> a #

caseByronToAlonzoOrBabbageEraOnwards :: (ByronToAlonzoEraConstraints era => ByronToAlonzoEra era -> a) -> (BabbageEraOnwardsConstraints era => BabbageEraOnwards era -> a) -> CardanoEra era -> a #

caseShelleyEraOnlyOrAllegraEraOnwards :: (ShelleyEraOnlyConstraints era => ShelleyEraOnly era -> a) -> (AllegraEraOnwardsConstraints era => AllegraEraOnwards era -> a) -> ShelleyBasedEra era -> a #

caseShelleyToAllegraOrMaryEraOnwards :: (ShelleyToAllegraEraConstraints era => ShelleyToAllegraEra era -> a) -> (MaryEraOnwardsConstraints era => MaryEraOnwards era -> a) -> ShelleyBasedEra era -> a #

caseShelleyToAlonzoOrBabbageEraOnwards :: (ShelleyToAlonzoEraConstraints era => ShelleyToAlonzoEra era -> a) -> (BabbageEraOnwardsConstraints era => BabbageEraOnwards era -> a) -> ShelleyBasedEra era -> a #

caseShelleyToBabbageOrConwayEraOnwards :: (ShelleyToBabbageEraConstraints era => ShelleyToBabbageEra era -> a) -> (ConwayEraOnwardsConstraints era => ConwayEraOnwards era -> a) -> ShelleyBasedEra era -> a #

caseShelleyToMaryOrAlonzoEraOnwards :: (ShelleyToMaryEraConstraints era => ShelleyToMaryEra era -> a) -> (AlonzoEraOnwardsConstraints era => AlonzoEraOnwards era -> a) -> ShelleyBasedEra era -> a #

cardanoEraConstraints :: CardanoEra era -> (CardanoEraConstraints era => a) -> a #

forEraInEon :: Eon eon => CardanoEra era -> a -> (eon era -> a) -> a #

forEraInEonMaybe :: Eon eon => CardanoEra era -> (eon era -> a) -> Maybe a #

forEraMaybeEon :: Eon eon => CardanoEra era -> Maybe (eon era) #

inAnyCardanoEra :: CardanoEra era -> thing era -> InAnyCardanoEra thing #

inEonForEraMaybe :: Eon eon => (eon era -> a) -> CardanoEra era -> Maybe a #

maybeEon :: (Eon eon, IsCardanoEra era) => Maybe (eon era) #

monoidForEraInEon :: (Eon eon, Monoid a) => CardanoEra era -> (eon era -> a) -> a #

monoidForEraInEonA :: (Eon eon, Applicative f, Monoid a) => CardanoEra era -> (eon era -> f a) -> f a #

asFeaturedInEra :: forall (eon :: Type -> Type) a era. Eon eon => a -> CardanoEra era -> Maybe (Featured eon era a) #

asFeaturedInShelleyBasedEra :: forall (eon :: Type -> Type) a era. Eon eon => a -> ShelleyBasedEra era -> Maybe (Featured eon era a) #

estimateTransactionFee :: ShelleyBasedEra era -> NetworkId -> Coin -> Coin -> Tx era -> Int -> Int -> Int -> Int -> Coin #

evaluateTransactionBalance :: ShelleyBasedEra era -> PParams (ShelleyLedgerEra era) -> Set PoolId -> Map StakeCredential Coin -> Map (Credential 'DRepRole StandardCrypto) Coin -> UTxO era -> TxBody era -> TxOutValue era #

renderSafeHashAsHex :: SafeHash c tag -> Text #

intoFile :: File content 'Out -> content -> (File content 'Out -> stream -> result) -> (content -> stream) -> result #

mapFile :: forall content (direction :: FileDirection). (FilePath -> FilePath) -> File content direction -> File content direction #

onlyIn :: File content 'InOut -> File content 'In #

onlyOut :: File content 'InOut -> File content 'Out #

readTextFile :: MonadIO m => File content 'In -> m (Either (FileError e) Text) #

writeByteStringFile :: MonadIO m => File content 'Out -> ByteString -> m (Either (FileError e) ()) #

writeByteStringOutput :: MonadIO m => Maybe (File content 'Out) -> ByteString -> m (Either (FileError e) ()) #

writeTextFile :: MonadIO m => File content 'Out -> Text -> m (Either (FileError e) ()) #

writeTextOutput :: MonadIO m => Maybe (File content 'Out) -> Text -> m (Either (FileError e) ()) #

writeSecrets :: FilePath -> [Char] -> [Char] -> (a -> ByteString) -> [a] -> IO () #

generateInsecureSigningKey :: (MonadIO m, Key keyrole, SerialiseAsRawBytes (SigningKey keyrole)) => StdGen -> AsType keyrole -> m (SigningKey keyrole, StdGen) #

generateSigningKey :: (MonadIO m, Key keyrole) => AsType keyrole -> m (SigningKey keyrole) #

foldBlocks :: forall a t (m :: Type -> Type). (Show a, MonadIOTransError FoldBlocksError t m) => NodeConfigFile 'In -> SocketPath -> ValidationMode -> a -> (Env -> LedgerState -> [LedgerEvent] -> BlockInMode -> a -> IO (a, FoldStatus)) -> t m a #

mkProtocolInfoCardano :: GenesisConfig -> (ProtocolInfo (HardForkBlock (CardanoEras StandardCrypto)), IO [BlockForging IO (HardForkBlock (CardanoEras StandardCrypto))]) #

readAlonzoGenesisConfig :: forall t (m :: Type -> Type). MonadIOTransError GenesisConfigError t m => NodeConfig -> t m AlonzoGenesis #

handleIOExceptionsLiftWith :: (MonadIOTransError e' t m, Exception e) => (e -> e') -> m a -> t m a #

handleIOExceptionsWith :: (MonadError e' m, MonadCatch m, Exception e) => (e -> e') -> m a -> m a #

hoistIOEither :: forall e t (m :: Type -> Type) a. MonadIOTransError e t m => IO (Either e a) -> t m a #

liftExceptT :: forall e t (m :: Type -> Type) a. MonadTransError e t m => ExceptT e m a -> t m a #

black :: Doc AnsiStyle -> Doc AnsiStyle #

cyan :: Doc AnsiStyle -> Doc AnsiStyle #

docToLazyText :: Doc AnsiStyle -> Text #

docToString :: Doc AnsiStyle -> String #

docToText :: Doc AnsiStyle -> Text #

magenta :: Doc AnsiStyle -> Doc AnsiStyle #

prettyException :: Exception a => a -> Doc ann #

pshow :: Show a => a -> Doc ann #

white :: Doc AnsiStyle -> Doc AnsiStyle #

yellow :: Doc AnsiStyle -> Doc AnsiStyle #

reflBlockType :: BlockType blk -> BlockType blk' -> Maybe (blk :~: blk') #

getProgress :: SlotNo -> EraHistory -> Either PastHorizonException (RelativeTime, SlotLength) #

getSlotForRelativeTime :: RelativeTime -> EraHistory -> Either PastHorizonException SlotNo #

queryConstitutionHash :: ShelleyBasedEra era -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Maybe (SafeHash (EraCrypto (ShelleyLedgerEra era)) AnchorData)))) #

queryDRepState :: ConwayEraOnwards era -> Set (Credential 'DRepRole StandardCrypto) -> LocalStateQueryExpr block point QueryInMode r IO (Either UnsupportedNtcVersionError (Either EraMismatch (Map (Credential 'DRepRole StandardCrypto) (DRepState StandardCrypto)))) #

writeFileJSON :: ToJSON a => FilePath -> a -> IO (Either (FileError ()) ()) #

writeTxFileTextEnvelopeCddl :: ShelleyBasedEra era -> File content 'Out -> Tx era -> IO (Either (FileError ()) ()) #

addTxIn :: (TxIn, BuildTxWith build (Witness WitCtxTxIn era)) -> TxBodyContent build era -> TxBodyContent build era #

addTxOut :: TxOut CtxTx era -> TxBodyContent build era -> TxBodyContent build era #

getTxId :: TxBody era -> TxId #

modTxIns :: (TxIns build era -> TxIns build era) -> TxBodyContent build era -> TxBodyContent build era #

modTxOuts :: ([TxOut CtxTx era] -> [TxOut CtxTx era]) -> TxBodyContent build era -> TxBodyContent build era #

setTxAuxScripts :: TxAuxScripts era -> TxBodyContent build era -> TxBodyContent build era #

setTxCertificates :: TxCertificates build era -> TxBodyContent build era -> TxBodyContent build era #

setTxFee :: TxFee era -> TxBodyContent build era -> TxBodyContent build era #

setTxIns :: TxIns build era -> TxBodyContent build era -> TxBodyContent build era #

setTxInsReference :: TxInsReference build era -> TxBodyContent build era -> TxBodyContent build era #

setTxMetadata :: TxMetadataInEra era -> TxBodyContent build era -> TxBodyContent build era #

setTxMintValue :: TxMintValue build era -> TxBodyContent build era -> TxBodyContent build era #

setTxOuts :: [TxOut CtxTx era] -> TxBodyContent build era -> TxBodyContent build era #

setTxWithdrawals :: TxWithdrawals build era -> TxBodyContent build era -> TxBodyContent build era #

getTxBody :: Tx era -> TxBody era #

getTxWitnesses :: Tx era -> [KeyWitness era] #

makeByronKeyWitness :: IsByronKey key => NetworkId -> Annotated Tx ByteString -> SigningKey key -> KeyWitness ByronEra #

makeShelleyBootstrapWitness :: ShelleyBasedEra era -> WitnessNetworkIdOrByronAddress -> TxBody era -> SigningKey ByronKey -> KeyWitness era #

makeSignedByronTransaction :: [KeyWitness era] -> Annotated Tx ByteString -> ATxAux ByteString #

makeSignedTransaction :: [KeyWitness era] -> TxBody era -> Tx era #

bounded :: (Bounded a, Integral a, Show a) => String -> ReadM a #

textShow :: Show a => a -> Text #

unsafeBoundedRational :: (HasCallStack, Typeable r, BoundedRational r) => Rational -> r #

vsep :: [Doc ann] -> Doc ann #

bimapExceptT :: forall (m :: Type -> Type) x y a b. Functor m => (x -> y) -> (a -> b) -> ExceptT x m a -> ExceptT y m b #

bracketExceptT :: forall (m :: Type -> Type) e a b c. Monad m => ExceptT e m a -> (a -> ExceptT e m b) -> (a -> ExceptT e m c) -> ExceptT e m c #

bracketExceptionT :: forall (m :: Type -> Type) e a c b. MonadMask m => ExceptT e m a -> (a -> ExceptT e m c) -> (a -> ExceptT e m b) -> ExceptT e m b #

catchExceptT :: (MonadCatch m, Exception e) => m a -> (e -> x) -> ExceptT x m a #

catchIOExceptT :: forall (m :: Type -> Type) a x. MonadIO m => IO a -> (IOException -> x) -> ExceptT x m a #

catchLeftT :: forall (m :: Type -> Type) e a. Monad m => ExceptT e m a -> (e -> ExceptT e m a) -> ExceptT e m a #

catchesExceptT :: (Foldable f, MonadCatch m) => m a -> f (Handler m x) -> ExceptT x m a #

exceptT :: Monad m => (x -> m b) -> (a -> m b) -> ExceptT x m a -> m b #

firstExceptT :: forall (m :: Type -> Type) x y a. Functor m => (x -> y) -> ExceptT x m a -> ExceptT y m a #

handleExceptT :: (MonadCatch m, Exception e) => (e -> x) -> m a -> ExceptT x m a #

handleIOExceptT :: forall (m :: Type -> Type) x a. MonadIO m => (IOException -> x) -> IO a -> ExceptT x m a #

handleLeftT :: forall (m :: Type -> Type) e a. Monad m => (e -> ExceptT e m a) -> ExceptT e m a -> ExceptT e m a #

handlesExceptT :: (Foldable f, MonadCatch m) => f (Handler m x) -> m a -> ExceptT x m a #

hoistEither :: forall (m :: Type -> Type) x a. Monad m => Either x a -> ExceptT x m a #

hoistExceptT :: (forall b. m b -> n b) -> ExceptT x m a -> ExceptT x n a #

hushM :: Monad m => Either e a -> (e -> m ()) -> m (Maybe a) #

newExceptT :: m (Either x a) -> ExceptT x m a #

onLeft :: forall e x (m :: Type -> Type) a. Monad m => (e -> ExceptT x m a) -> ExceptT x m (Either e a) -> ExceptT x m a #

onNothing :: forall x (m :: Type -> Type) a. Monad m => ExceptT x m a -> ExceptT x m (Maybe a) -> ExceptT x m a #

secondExceptT :: forall (m :: Type -> Type) a b x. Functor m => (a -> b) -> ExceptT x m a -> ExceptT x m b #

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

castSigningKey :: CastSigningKeyRole keyroleA keyroleB => SigningKey keyroleA -> SigningKey keyroleB #

castVerificationKey :: CastVerificationKeyRole keyroleA keyroleB => VerificationKey keyroleA -> VerificationKey keyroleB #