ouroboros-consensus-cardano-0.12.1.0: The instantation of the Ouroboros consensus layer used by Cardano
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Consensus.Shelley.Ledger.Block

Synopsis

Documentation

class HasHeader (Header blk) => GetHeader blk where #

Methods

getHeader :: blk -> Header blk #

blockMatchesHeader :: Header blk -> blk -> Bool #

headerIsEBB :: Header blk -> Maybe EpochNo #

Instances

Instances details
GetHeader ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

ShelleyCompatible proto era => GetHeader (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeader :: ShelleyBlock proto era -> Header (ShelleyBlock proto era) #

blockMatchesHeader :: Header (ShelleyBlock proto era) -> ShelleyBlock proto era -> Bool #

headerIsEBB :: Header (ShelleyBlock proto era) -> Maybe EpochNo #

data family Header blk #

Instances

Instances details
Inject Header 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

Methods

inject :: forall x (xs :: [Type]). CanHardFork xs => Exactly xs Bound -> Index xs x -> Header x -> Header (HardForkBlock xs)

HasNestedContent Header ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Serialisation

Methods

unnest :: Header ByronBlock -> DepPair (NestedCtxt Header ByronBlock)

nest :: DepPair (NestedCtxt Header ByronBlock) -> Header ByronBlock

ReconstructNestedCtxt Header ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

reconstructPrefixLen :: proxy (Header ByronBlock) -> PrefixLen

reconstructNestedCtxt :: proxy (Header ByronBlock) -> ShortByteString -> SizeInBytes -> SomeSecond (NestedCtxt Header) ByronBlock

SerialiseNodeToNode ByronBlock (Header ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig ByronBlock -> BlockNodeToNodeVersion ByronBlock -> Header ByronBlock -> Encoding

decodeNodeToNode :: CodecConfig ByronBlock -> BlockNodeToNodeVersion ByronBlock -> forall s. Decoder s (Header ByronBlock)

HasHeader blk => StandardHash (Header blk :: Type) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

ShowProxy (Header ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

(Typeable era, Typeable proto) => ShowProxy (Header (ShelleyBlock proto era) :: Type) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showProxy :: Proxy (Header (ShelleyBlock proto era)) -> String

ShelleyBasedEra era => ReconstructNestedCtxt Header (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

reconstructPrefixLen :: proxy (Header (ShelleyBlock proto era)) -> PrefixLen

reconstructNestedCtxt :: proxy (Header (ShelleyBlock proto era)) -> ShortByteString -> SizeInBytes -> SomeSecond (NestedCtxt Header) (ShelleyBlock proto era)

Generic (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

Associated Types

type Rep (Header ByronBlock) :: Type -> Type Source #

Generic (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type Rep (Header (ShelleyBlock proto era)) :: Type -> Type Source #

Methods

from :: Header (ShelleyBlock proto era) -> Rep (Header (ShelleyBlock proto era)) x Source #

to :: Rep (Header (ShelleyBlock proto era)) x -> Header (ShelleyBlock proto era) Source #

Show (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

ShelleyCompatible proto era => Show (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrec :: Int -> Header (ShelleyBlock proto era) -> ShowS Source #

show :: Header (ShelleyBlock proto era) -> String Source #

showList :: [Header (ShelleyBlock proto era)] -> ShowS Source #

ShelleyCompatible proto era => DecCBOR (Annotator (Header (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

decCBOR :: Decoder s (Annotator (Header (ShelleyBlock proto era)))

dropCBOR :: Proxy (Annotator (Header (ShelleyBlock proto era))) -> Decoder s ()

label :: Proxy (Annotator (Header (ShelleyBlock proto era))) -> Text

ShelleyCompatible proto era => EncCBOR (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

encCBOR :: Header (ShelleyBlock proto era) -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Header (ShelleyBlock proto era)) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Header (ShelleyBlock proto era)] -> Size

Eq (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

ShelleyCompatible proto era => Eq (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

(==) :: Header (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> Bool Source #

(/=) :: Header (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> Bool Source #

NoThunks (Header ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

Methods

noThunks :: Context -> Header ByronBlock -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Header ByronBlock -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Header ByronBlock) -> String

ShelleyCompatible proto era => NoThunks (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

noThunks :: Context -> Header (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Header (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Header (ShelleyBlock proto era)) -> String

SignedHeader (ShelleyProtocolHeader proto) => SignedHeader (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

Methods

headerSigned :: Header (ShelleyBlock proto era) -> Signed (Header (ShelleyBlock proto era))

Condense (Header ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

ShelleyCompatible proto era => Condense (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

condense :: Header (ShelleyBlock proto era) -> String

HasHeader (Header ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

Methods

getHeaderFields :: Header ByronBlock -> HeaderFields (Header ByronBlock)

ShelleyCompatible proto era => HasHeader (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeaderFields :: Header (ShelleyBlock proto era) -> HeaderFields (Header (ShelleyBlock proto era))

DecodeDiskDep (NestedCtxt Header) ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

decodeDiskDep :: CodecConfig ByronBlock -> NestedCtxt Header ByronBlock a -> forall s. Decoder s (ByteString -> a)

DecodeDiskDepIx (NestedCtxt Header) ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

decodeDiskDepIx :: CodecConfig ByronBlock -> Decoder s (SomeSecond (NestedCtxt Header) ByronBlock)

EncodeDiskDep (NestedCtxt Header) ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeDiskDep :: CodecConfig ByronBlock -> NestedCtxt Header ByronBlock a -> a -> Encoding

EncodeDiskDepIx (NestedCtxt Header) ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

encodeDiskDepIx :: CodecConfig ByronBlock -> SomeSecond (NestedCtxt Header) ByronBlock -> Encoding

ShelleyCompatible proto era => DecodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskDep :: CodecConfig (ShelleyBlock proto era) -> NestedCtxt Header (ShelleyBlock proto era) a -> forall s. Decoder s (ByteString -> a)

ShelleyBasedEra era => DecodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskDepIx :: CodecConfig (ShelleyBlock proto era) -> Decoder s (SomeSecond (NestedCtxt Header) (ShelleyBlock proto era))

ShelleyCompatible proto era => EncodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskDep :: CodecConfig (ShelleyBlock proto era) -> NestedCtxt Header (ShelleyBlock proto era) a -> a -> Encoding

ShelleyBasedEra era => EncodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskDepIx :: CodecConfig (ShelleyBlock proto era) -> SomeSecond (NestedCtxt Header) (ShelleyBlock proto era) -> Encoding

ShelleyCompatible proto era => SerialiseNodeToNode (ShelleyBlock proto era) (Header (ShelleyBlock proto era))

CBOR-in-CBOR to be compatible with the wrapped (Serialised) variant.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> Encoding

decodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> forall s. Decoder s (Header (ShelleyBlock proto era))

ShelleyCompatible proto era => EncodeDisk (ShelleyBlock proto era) (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDisk :: CodecConfig (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> Encoding

ShelleyCompatible proto era => DecodeDisk (ShelleyBlock proto era) (ByteString -> Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDisk :: CodecConfig (ShelleyBlock proto era) -> forall s. Decoder s (ByteString -> Header (ShelleyBlock proto era))

data Header ByronBlock Source #

Byron header

See ByronBlock for comments on why we cache certain values.

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

data Header ByronBlock = ByronHeader {}
type HeaderHash (Header blk :: Type) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type HeaderHash (Header blk :: Type) = HeaderHash blk
type Rep (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

type Rep (Header ByronBlock) = D1 ('MetaData "Header" "Ouroboros.Consensus.Byron.Ledger.Block" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ByronHeader" 'PrefixI 'True) ((S1 ('MetaSel ('Just "byronHeaderRaw") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ABlockOrBoundaryHdr ByteString)) :*: S1 ('MetaSel ('Just "byronHeaderSlotNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo)) :*: (S1 ('MetaSel ('Just "byronHeaderHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByronHash) :*: S1 ('MetaSel ('Just "byronHeaderBlockSizeHint") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SizeInBytes))))
type Rep (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type Rep (Header (ShelleyBlock proto era)) = D1 ('MetaData "Header" "Ouroboros.Consensus.Shelley.Ledger.Block" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyHeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyHeaderRaw") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShelleyProtocolHeader proto)) :*: S1 ('MetaSel ('Just "shelleyHeaderHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShelleyHash (ProtoCrypto proto)))))
type BlockProtocol (Header blk) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

type BlockProtocol (Header blk) = BlockProtocol blk
newtype Header (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

newtype Header (HardForkBlock xs) = HardForkHeader {}
type Signed (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

type Signed (Header (ShelleyBlock proto era)) = Signed (ShelleyProtocolHeader proto)
data Header (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

data family NestedCtxt_ blk :: (Type -> Type) -> Type -> Type #

Instances

Instances details
SameDepIndex (NestedCtxt_ ByronBlock f) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Serialisation

SameDepIndex (NestedCtxt_ (ShelleyBlock proto era) f) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

sameDepIndex :: NestedCtxt_ (ShelleyBlock proto era) f a -> NestedCtxt_ (ShelleyBlock proto era) f b -> Maybe (a :~: b)

TrivialDependency (NestedCtxt_ (ShelleyBlock proto era) f) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f)

Methods

hasSingleIndex :: NestedCtxt_ (ShelleyBlock proto era) f a -> NestedCtxt_ (ShelleyBlock proto era) f b -> a :~: b

indexIsTrivial :: NestedCtxt_ (ShelleyBlock proto era) f (TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f))

Show (NestedCtxt_ ByronBlock f a) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Serialisation

Show (NestedCtxt_ (ShelleyBlock proto era) f a) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrec :: Int -> NestedCtxt_ (ShelleyBlock proto era) f a -> ShowS Source #

show :: NestedCtxt_ (ShelleyBlock proto era) f a -> String Source #

showList :: [NestedCtxt_ (ShelleyBlock proto era) f a] -> ShowS Source #

data NestedCtxt_ ByronBlock f a Source #

Since the Byron header does not contain the size, we include it in the nested type instead.

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Serialisation

data NestedCtxt_ (HardForkBlock xs) a b 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

data NestedCtxt_ (HardForkBlock xs) a b where
data NestedCtxt_ (ShelleyBlock proto era) f a Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

data NestedCtxt_ (ShelleyBlock proto era) f a where
type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) = f (ShelleyBlock proto era)

class (EraSegWits era, EraGov era, ApplyTx era, ApplyBlock era, EraTransition era, GetLedgerView era, NoThunks (StashedAVVMAddresses era), EncCBOR (StashedAVVMAddresses era), DecCBOR (StashedAVVMAddresses era), Show (StashedAVVMAddresses era), Eq (StashedAVVMAddresses era), DecCBOR (PredicateFailure (EraRule "LEDGER" era)), EncCBOR (PredicateFailure (EraRule "LEDGER" era)), DecCBOR (PredicateFailure (EraRule "UTXOW" era)), EncCBOR (PredicateFailure (EraRule "UTXOW" era)), DSignable (EraCrypto era) (Hash (EraCrypto era) EraIndependentTxBody), NoThunks (PredicateFailure (EraRule "BBODY" era)), NoThunks (TranslationContext era)) => ShelleyBasedEra era Source #

Consensus often needs some more functionality than the ledger currently provides.

Either the functionality shouldn't or can't live in the ledger, in which case it can be part and remain part of ShelleyBasedEra. Or, the functionality should live in the ledger, but hasn't yet been added to the ledger, or it hasn't yet been propagated to this repository, in which case it can be added to this class until that is the case.

If this class becomes redundant, We can move it to ledger and re-export it from here.

TODO Currently we include some constraints on the update state which are needed to determine the hard fork point. In the future this should be replaced with an appropriate API - see https://github.com/input-output-hk/ouroboros-network/issues/2890

Instances

Instances details
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) => ShelleyBasedEra (AllegraEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName :: proxy (AllegraEra c) -> Text Source #

applyShelleyBasedTx :: Globals -> LedgerEnv (AllegraEra c) -> LedgerState (AllegraEra c) -> WhetherToIntervene -> Tx (AllegraEra c) -> Except (ApplyTxError (AllegraEra c)) (LedgerState (AllegraEra c), Validated (Tx (AllegraEra c))) Source #

getProposedProtocolVersion :: PParamsUpdate (AllegraEra c) -> Maybe ProtVer Source #

(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) => ShelleyBasedEra (AlonzoEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName :: proxy (AlonzoEra c) -> Text Source #

applyShelleyBasedTx :: Globals -> LedgerEnv (AlonzoEra c) -> LedgerState (AlonzoEra c) -> WhetherToIntervene -> Tx (AlonzoEra c) -> Except (ApplyTxError (AlonzoEra c)) (LedgerState (AlonzoEra c), Validated (Tx (AlonzoEra c))) Source #

getProposedProtocolVersion :: PParamsUpdate (AlonzoEra c) -> Maybe ProtVer Source #

PraosCrypto c => ShelleyBasedEra (BabbageEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName :: proxy (BabbageEra c) -> Text Source #

applyShelleyBasedTx :: Globals -> LedgerEnv (BabbageEra c) -> LedgerState (BabbageEra c) -> WhetherToIntervene -> Tx (BabbageEra c) -> Except (ApplyTxError (BabbageEra c)) (LedgerState (BabbageEra c), Validated (Tx (BabbageEra c))) Source #

getProposedProtocolVersion :: PParamsUpdate (BabbageEra c) -> Maybe ProtVer Source #

PraosCrypto c => ShelleyBasedEra (ConwayEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName :: proxy (ConwayEra c) -> Text Source #

applyShelleyBasedTx :: Globals -> LedgerEnv (ConwayEra c) -> LedgerState (ConwayEra c) -> WhetherToIntervene -> Tx (ConwayEra c) -> Except (ApplyTxError (ConwayEra c)) (LedgerState (ConwayEra c), Validated (Tx (ConwayEra c))) Source #

getProposedProtocolVersion :: PParamsUpdate (ConwayEra c) -> Maybe ProtVer Source #

(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) => ShelleyBasedEra (MaryEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName :: proxy (MaryEra c) -> Text Source #

applyShelleyBasedTx :: Globals -> LedgerEnv (MaryEra c) -> LedgerState (MaryEra c) -> WhetherToIntervene -> Tx (MaryEra c) -> Except (ApplyTxError (MaryEra c)) (LedgerState (MaryEra c), Validated (Tx (MaryEra c))) Source #

getProposedProtocolVersion :: PParamsUpdate (MaryEra c) -> Maybe ProtVer Source #

(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) => ShelleyBasedEra (ShelleyEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName :: proxy (ShelleyEra c) -> Text Source #

applyShelleyBasedTx :: Globals -> LedgerEnv (ShelleyEra c) -> LedgerState (ShelleyEra c) -> WhetherToIntervene -> Tx (ShelleyEra c) -> Except (ApplyTxError (ShelleyEra c)) (LedgerState (ShelleyEra c), Validated (Tx (ShelleyEra c))) Source #

getProposedProtocolVersion :: PParamsUpdate (ShelleyEra c) -> Maybe ProtVer Source #

data ShelleyBlock proto era Source #

Shelley-based block type.

This block is parametrised over both the (ledger) era and the protocol.

Constructors

ShelleyBlock 

Instances

Instances details
(Typeable era, Typeable proto) => ShowProxy (Header (ShelleyBlock proto era) :: Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showProxy :: Proxy (Header (ShelleyBlock proto era)) -> String

(Typeable era, Typeable proto) => ShowProxy (Validated (GenTx (ShelleyBlock proto era)) :: Type) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxy :: Proxy (Validated (GenTx (ShelleyBlock proto era))) -> String

(Typeable era, Typeable proto) => ShowProxy (GenTx (ShelleyBlock proto era) :: Type) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxy :: Proxy (GenTx (ShelleyBlock proto era)) -> String

(Typeable era, Typeable proto) => ShowProxy (TxId (GenTx (ShelleyBlock proto era)) :: Type) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxy :: Proxy (TxId (GenTx (ShelleyBlock proto era))) -> String

HasNestedContent f (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

unnest :: f (ShelleyBlock proto era) -> DepPair (NestedCtxt f (ShelleyBlock proto era))

nest :: DepPair (NestedCtxt f (ShelleyBlock proto era)) -> f (ShelleyBlock proto era)

ShelleyBasedEra era => ReconstructNestedCtxt Header (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

reconstructPrefixLen :: proxy (Header (ShelleyBlock proto era)) -> PrefixLen

reconstructNestedCtxt :: proxy (Header (ShelleyBlock proto era)) -> ShortByteString -> SizeInBytes -> SomeSecond (NestedCtxt Header) (ShelleyBlock proto era)

ShelleyCompatible proto era => StandardHash (ShelleyBlock proto era :: Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

(Typeable era, Typeable proto) => ShowProxy (ShelleyBlock proto era :: Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showProxy :: Proxy (ShelleyBlock proto era) -> String

(ShelleyBasedEra era, TranslateEra era (ShelleyTip proto), TranslateEra era NewEpochState, TranslationError era NewEpochState ~ Void) => TranslateEra era (LedgerState :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (LedgerState :.: ShelleyBlock proto)

Methods

translateEra :: TranslationContext era -> (LedgerState :.: ShelleyBlock proto) (PreviousEra era) -> Except (TranslationError era (LedgerState :.: ShelleyBlock proto)) ((LedgerState :.: ShelleyBlock proto) era)

(ShelleyBasedEra era, TranslateEra era WrapTx) => TranslateEra era (GenTx :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (GenTx :.: ShelleyBlock proto)

Methods

translateEra :: TranslationContext era -> (GenTx :.: ShelleyBlock proto) (PreviousEra era) -> Except (TranslationError era (GenTx :.: ShelleyBlock proto)) ((GenTx :.: ShelleyBlock proto) era)

(ShelleyBasedEra era, TranslateEra era WrapTx) => TranslateEra era (WrapValidatedGenTx :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (WrapValidatedGenTx :.: ShelleyBlock proto)

Methods

translateEra :: TranslationContext era -> (WrapValidatedGenTx :.: ShelleyBlock proto) (PreviousEra era) -> Except (TranslationError era (WrapValidatedGenTx :.: ShelleyBlock proto)) ((WrapValidatedGenTx :.: ShelleyBlock proto) era)

Generic (BlockConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (BlockConfig (ShelleyBlock proto era)) :: Type -> Type Source #

Methods

from :: BlockConfig (ShelleyBlock proto era) -> Rep (BlockConfig (ShelleyBlock proto era)) x Source #

to :: Rep (BlockConfig (ShelleyBlock proto era)) x -> BlockConfig (ShelleyBlock proto era) Source #

Generic (CodecConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (CodecConfig (ShelleyBlock proto era)) :: Type -> Type Source #

Methods

from :: CodecConfig (ShelleyBlock proto era) -> Rep (CodecConfig (ShelleyBlock proto era)) x Source #

to :: Rep (CodecConfig (ShelleyBlock proto era)) x -> CodecConfig (ShelleyBlock proto era) Source #

Generic (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type Rep (Header (ShelleyBlock proto era)) :: Type -> Type Source #

Methods

from :: Header (ShelleyBlock proto era) -> Rep (Header (ShelleyBlock proto era)) x Source #

to :: Rep (Header (ShelleyBlock proto era)) x -> Header (ShelleyBlock proto era) Source #

Generic (StorageConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (StorageConfig (ShelleyBlock proto era)) :: Type -> Type Source #

Methods

from :: StorageConfig (ShelleyBlock proto era) -> Rep (StorageConfig (ShelleyBlock proto era)) x Source #

to :: Rep (StorageConfig (ShelleyBlock proto era)) x -> StorageConfig (ShelleyBlock proto era) Source #

Generic (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type Rep (Validated (GenTx (ShelleyBlock proto era))) :: Type -> Type Source #

Methods

from :: Validated (GenTx (ShelleyBlock proto era)) -> Rep (Validated (GenTx (ShelleyBlock proto era))) x Source #

to :: Rep (Validated (GenTx (ShelleyBlock proto era))) x -> Validated (GenTx (ShelleyBlock proto era)) Source #

Generic (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (LedgerState (ShelleyBlock proto era)) :: Type -> Type Source #

Methods

from :: LedgerState (ShelleyBlock proto era) -> Rep (LedgerState (ShelleyBlock proto era)) x Source #

to :: Rep (LedgerState (ShelleyBlock proto era)) x -> LedgerState (ShelleyBlock proto era) Source #

Generic (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type Rep (GenTx (ShelleyBlock proto era)) :: Type -> Type Source #

Methods

from :: GenTx (ShelleyBlock proto era) -> Rep (GenTx (ShelleyBlock proto era)) x Source #

to :: Rep (GenTx (ShelleyBlock proto era)) x -> GenTx (ShelleyBlock proto era) Source #

Generic (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) :: Type -> Type Source #

Methods

from :: Ticked (LedgerState (ShelleyBlock proto era)) -> Rep (Ticked (LedgerState (ShelleyBlock proto era))) x Source #

to :: Rep (Ticked (LedgerState (ShelleyBlock proto era))) x -> Ticked (LedgerState (ShelleyBlock proto era)) Source #

ShelleyBasedEra era => Show (BlockConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

ShelleyCompatible proto era => Show (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrec :: Int -> Header (ShelleyBlock proto era) -> ShowS Source #

show :: Header (ShelleyBlock proto era) -> String Source #

showList :: [Header (ShelleyBlock proto era)] -> ShowS Source #

ShelleyBasedEra era => Show (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

ShelleyBasedEra era => Show (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyBasedEra era => Show (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrec :: Int -> GenTx (ShelleyBlock proto era) -> ShowS Source #

show :: GenTx (ShelleyBlock proto era) -> String Source #

showList :: [GenTx (ShelleyBlock proto era)] -> ShowS Source #

Show (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrec :: Int -> GenTxId (ShelleyBlock proto era) -> ShowS Source #

show :: GenTxId (ShelleyBlock proto era) -> String Source #

showList :: [GenTxId (ShelleyBlock proto era)] -> ShowS Source #

ShelleyCompatible proto era => FromCBOR (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

fromCBOR :: Decoder s (GenTx (ShelleyBlock proto era))

label :: Proxy (GenTx (ShelleyBlock proto era)) -> Text

ShelleyCompatible proto era => ToCBOR (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

toCBOR :: GenTx (ShelleyBlock proto era) -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy (GenTx (ShelleyBlock proto era)) -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [GenTx (ShelleyBlock proto era)] -> Size

ShelleyCompatible proto era => DecCBOR (Annotator (Header (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

decCBOR :: Decoder s (Annotator (Header (ShelleyBlock proto era)))

dropCBOR :: Proxy (Annotator (Header (ShelleyBlock proto era))) -> Decoder s ()

label :: Proxy (Annotator (Header (ShelleyBlock proto era))) -> Text

ShelleyCompatible proto era => DecCBOR (Annotator (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

decCBOR :: Decoder s (Annotator (ShelleyBlock proto era))

dropCBOR :: Proxy (Annotator (ShelleyBlock proto era)) -> Decoder s ()

label :: Proxy (Annotator (ShelleyBlock proto era)) -> Text

(Crypto (EraCrypto era), Typeable era, Typeable proto) => DecCBOR (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

decCBOR :: Decoder s (TxId (GenTx (ShelleyBlock proto era)))

dropCBOR :: Proxy (TxId (GenTx (ShelleyBlock proto era))) -> Decoder s ()

label :: Proxy (TxId (GenTx (ShelleyBlock proto era))) -> Text

ShelleyCompatible proto era => EncCBOR (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

encCBOR :: Header (ShelleyBlock proto era) -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (Header (ShelleyBlock proto era)) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [Header (ShelleyBlock proto era)] -> Size

(Crypto (EraCrypto era), Typeable era, Typeable proto) => EncCBOR (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

encCBOR :: TxId (GenTx (ShelleyBlock proto era)) -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (TxId (GenTx (ShelleyBlock proto era))) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [TxId (GenTx (ShelleyBlock proto era))] -> Size

ShelleyCompatible proto era => Eq (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

(==) :: Header (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> Bool Source #

(/=) :: Header (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> Bool Source #

ShelleyBasedEra era => Eq (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

(==) :: Validated (GenTx (ShelleyBlock proto era)) -> Validated (GenTx (ShelleyBlock proto era)) -> Bool Source #

(/=) :: Validated (GenTx (ShelleyBlock proto era)) -> Validated (GenTx (ShelleyBlock proto era)) -> Bool Source #

ShelleyBasedEra era => Eq (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

(==) :: LedgerState (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> Bool Source #

(/=) :: LedgerState (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> Bool Source #

ShelleyBasedEra era => Eq (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

(==) :: GenTx (ShelleyBlock proto era) -> GenTx (ShelleyBlock proto era) -> Bool Source #

(/=) :: GenTx (ShelleyBlock proto era) -> GenTx (ShelleyBlock proto era) -> Bool Source #

Eq (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

(==) :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Bool Source #

(/=) :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Bool Source #

Ord (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

compare :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Ordering Source #

(<) :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Bool Source #

(<=) :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Bool Source #

(>) :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Bool Source #

(>=) :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> Bool Source #

max :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) Source #

min :: TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) -> TxId (GenTx (ShelleyBlock proto era)) Source #

ShelleyBasedEra era => NoThunks (BlockConfig (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

noThunks :: Context -> BlockConfig (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> BlockConfig (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (BlockConfig (ShelleyBlock proto era)) -> String

NoThunks (CodecConfig (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

noThunks :: Context -> CodecConfig (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> CodecConfig (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (CodecConfig (ShelleyBlock proto era)) -> String

ShelleyCompatible proto era => NoThunks (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

noThunks :: Context -> Header (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Header (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Header (ShelleyBlock proto era)) -> String

NoThunks (StorageConfig (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

noThunks :: Context -> StorageConfig (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> StorageConfig (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (StorageConfig (ShelleyBlock proto era)) -> String

ShelleyBasedEra era => NoThunks (Validated (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunks :: Context -> Validated (GenTx (ShelleyBlock proto era)) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Validated (GenTx (ShelleyBlock proto era)) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Validated (GenTx (ShelleyBlock proto era))) -> String

ShelleyBasedEra era => NoThunks (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks :: Context -> LedgerState (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> LedgerState (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (LedgerState (ShelleyBlock proto era)) -> String

ShelleyBasedEra era => NoThunks (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunks :: Context -> GenTx (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> GenTx (ShelleyBlock proto era) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (GenTx (ShelleyBlock proto era)) -> String

NoThunks (TxId (GenTx (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunks :: Context -> TxId (GenTx (ShelleyBlock proto era)) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> TxId (GenTx (ShelleyBlock proto era)) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (TxId (GenTx (ShelleyBlock proto era))) -> String

ShelleyBasedEra era => NoThunks (Ticked (LedgerState (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks :: Context -> Ticked (LedgerState (ShelleyBlock proto era)) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Ticked (LedgerState (ShelleyBlock proto era)) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Ticked (LedgerState (ShelleyBlock proto era))) -> String

CardanoHardForkConstraints c => CanHardFork (CardanoEras c) 
Instance details

Defined in Ouroboros.Consensus.Cardano.CanHardFork

Methods

hardForkEraTranslation :: EraTranslation (CardanoEras c)

hardForkChainSel :: Tails AcrossEraSelection (CardanoEras c)

hardForkInjectTxs :: InPairs (RequiringBoth WrapLedgerConfig (Product2 InjectTx InjectValidatedTx)) (CardanoEras c)

CardanoHardForkConstraints c => CondenseConstraints (CardanoBlock c) 
Instance details

Defined in Ouroboros.Consensus.Cardano.Condense

CardanoHardForkConstraints c => SerialiseHFC (CardanoEras c)

Important: we need to maintain binary compatibility with Byron blocks, as they are already stored on disk.

We also want to be able to efficiently detect (without having to peek far ahead) whether we're dealing with a Byron or Shelley block, so that we can invoke the right decoder. We plan to have a few more hard forks after Shelley (Goguen, Basho, Voltaire), so we want a future-proof envelope for distinguishing the different block types, i.e., a byte indicating the era.

Byron does not provide such an envelope. However, a Byron block is a CBOR 2-tuple with the first element being a tag (Word: 0 = EBB; 1 = regular block) and the second being the payload. We can easily extend this encoding format with support for Shelley, Goguen, etc.

We encode a CardanoBlock as the same CBOR 2-tuple as a Byron block, but we use the tags after 1 for the hard forks after Byron:

  1. Byron EBB
  2. Byron regular block
  3. Shelley block
  4. Allegra block
  5. Mary block
  6. Goguen block
  7. etc.

For more details, see: https://github.com/input-output-hk/ouroboros-network/pull/1175#issuecomment-558147194

Instance details

Defined in Ouroboros.Consensus.Cardano.Node

Methods

encodeDiskHfcBlock :: CodecConfig (HardForkBlock (CardanoEras c)) -> HardForkBlock (CardanoEras c) -> Encoding

decodeDiskHfcBlock :: CodecConfig (HardForkBlock (CardanoEras c)) -> forall s. Decoder s (ByteString -> HardForkBlock (CardanoEras c))

reconstructHfcPrefixLen :: proxy (Header (HardForkBlock (CardanoEras c))) -> PrefixLen

reconstructHfcNestedCtxt :: proxy (Header (HardForkBlock (CardanoEras c))) -> ShortByteString -> SizeInBytes -> SomeSecond (NestedCtxt Header) (HardForkBlock (CardanoEras c))

getHfcBinaryBlockInfo :: HardForkBlock (CardanoEras c) -> BinaryBlockInfo

estimateHfcBlockSize :: Header (HardForkBlock (CardanoEras c)) -> SizeInBytes

GetTip (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTip :: LedgerState (ShelleyBlock proto era) -> Point (LedgerState (ShelleyBlock proto era))

GetTip (Ticked (LedgerState (ShelleyBlock proto era))) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTip :: Ticked (LedgerState (ShelleyBlock proto era)) -> Point (Ticked (LedgerState (ShelleyBlock proto era)))

ShelleyBasedEra era => IsLedger (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type LedgerErr (LedgerState (ShelleyBlock proto era))

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era))

Methods

applyChainTickLedgerResult :: LedgerCfg (LedgerState (ShelleyBlock proto era)) -> SlotNo -> LedgerState (ShelleyBlock proto era) -> LedgerResult (LedgerState (ShelleyBlock proto era)) (Ticked (LedgerState (ShelleyBlock proto era)))

ShelleyBasedEra era => HasTxId (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

txId :: GenTx (ShelleyBlock proto era) -> TxId (GenTx (ShelleyBlock proto era))

CardanoHardForkConstraints c => SupportedNetworkProtocolVersion (CardanoBlock c) 
Instance details

Defined in Ouroboros.Consensus.Cardano.Node

Methods

supportedNodeToNodeVersions :: Proxy (CardanoBlock c) -> Map NodeToNodeVersion (BlockNodeToNodeVersion (CardanoBlock c))

supportedNodeToClientVersions :: Proxy (CardanoBlock c) -> Map NodeToClientVersion (BlockNodeToClientVersion (CardanoBlock c))

latestReleasedNodeVersion :: Proxy (CardanoBlock c) -> (Maybe NodeToNodeVersion, Maybe NodeToClientVersion)

SignedHeader (ShelleyProtocolHeader proto) => SignedHeader (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

Methods

headerSigned :: Header (ShelleyBlock proto era) -> Signed (Header (ShelleyBlock proto era))

ShelleyCompatible proto era => Condense (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

condense :: Header (ShelleyBlock proto era) -> String

ShelleyBasedEra era => Condense (GenTx (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

condense :: GenTx (ShelleyBlock proto era) -> String

Condense (GenTxId (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

condense :: GenTxId (ShelleyBlock proto era) -> String

SameDepIndex (BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

sameDepIndex :: BlockQuery (ShelleyBlock proto era) a -> BlockQuery (ShelleyBlock proto era) b -> Maybe (a :~: b)

ShelleyCompatible proto era => HasHeader (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeaderFields :: Header (ShelleyBlock proto era) -> HeaderFields (Header (ShelleyBlock proto era))

ShelleyCompatible proto era => ShowQuery (BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showResult :: BlockQuery (ShelleyBlock proto era) result -> result -> String

ShelleyCompatible proto era => ApplyBlock (LedgerState (ShelleyBlock proto era)) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

applyBlockLedgerResult :: LedgerCfg (LedgerState (ShelleyBlock proto era)) -> ShelleyBlock proto era -> Ticked (LedgerState (ShelleyBlock proto era)) -> Except (LedgerErr (LedgerState (ShelleyBlock proto era))) (LedgerResult (LedgerState (ShelleyBlock proto era)) (LedgerState (ShelleyBlock proto era)))

reapplyBlockLedgerResult :: LedgerCfg (LedgerState (ShelleyBlock proto era)) -> ShelleyBlock proto era -> Ticked (LedgerState (ShelleyBlock proto era)) -> LedgerResult (LedgerState (ShelleyBlock proto era)) (LedgerState (ShelleyBlock proto era))

ShelleyCompatible proto era => DecodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskDep :: CodecConfig (ShelleyBlock proto era) -> NestedCtxt Header (ShelleyBlock proto era) a -> forall s. Decoder s (ByteString -> a)

ShelleyBasedEra era => DecodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskDepIx :: CodecConfig (ShelleyBlock proto era) -> Decoder s (SomeSecond (NestedCtxt Header) (ShelleyBlock proto era))

ShelleyCompatible proto era => EncodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskDep :: CodecConfig (ShelleyBlock proto era) -> NestedCtxt Header (ShelleyBlock proto era) a -> a -> Encoding

ShelleyBasedEra era => EncodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskDepIx :: CodecConfig (ShelleyBlock proto era) -> SomeSecond (NestedCtxt Header) (ShelleyBlock proto era) -> Encoding

Show (BlockQuery (ShelleyBlock proto era) result) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showsPrec :: Int -> BlockQuery (ShelleyBlock proto era) result -> ShowS Source #

show :: BlockQuery (ShelleyBlock proto era) result -> String Source #

showList :: [BlockQuery (ShelleyBlock proto era) result] -> ShowS Source #

ShelleyCompatible proto era => Show (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrec :: Int -> ShelleyBlock proto era -> ShowS Source #

show :: ShelleyBlock proto era -> String Source #

showList :: [ShelleyBlock proto era] -> ShowS Source #

ShelleyCompatible proto era => EncCBOR (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

encCBOR :: ShelleyBlock proto era -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ShelleyBlock proto era) -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [ShelleyBlock proto era] -> Size

Eq (BlockQuery (ShelleyBlock proto era) result) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

(==) :: BlockQuery (ShelleyBlock proto era) result -> BlockQuery (ShelleyBlock proto era) result -> Bool Source #

(/=) :: BlockQuery (ShelleyBlock proto era) result -> BlockQuery (ShelleyBlock proto era) result -> Bool Source #

ShelleyCompatible proto era => Eq (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

(==) :: ShelleyBlock proto era -> ShelleyBlock proto era -> Bool Source #

(/=) :: ShelleyBlock proto era -> ShelleyBlock proto era -> Bool Source #

ShelleyCompatible proto era => ConvertRawHash (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

toRawHash :: proxy (ShelleyBlock proto era) -> HeaderHash (ShelleyBlock proto era) -> ByteString

fromRawHash :: proxy (ShelleyBlock proto era) -> ByteString -> HeaderHash (ShelleyBlock proto era)

toShortRawHash :: proxy (ShelleyBlock proto era) -> HeaderHash (ShelleyBlock proto era) -> ShortByteString

fromShortRawHash :: proxy (ShelleyBlock proto era) -> ShortByteString -> HeaderHash (ShelleyBlock proto era)

hashSize :: proxy (ShelleyBlock proto era) -> Word32

ShelleyCompatible proto era => GetHeader (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeader :: ShelleyBlock proto era -> Header (ShelleyBlock proto era) #

blockMatchesHeader :: Header (ShelleyBlock proto era) -> ShelleyBlock proto era -> Bool #

headerIsEBB :: Header (ShelleyBlock proto era) -> Maybe EpochNo #

ShelleyCompatible proto era => GetPrevHash (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

headerPrevHash :: Header (ShelleyBlock proto era) -> ChainHash (ShelleyBlock proto era)

ShelleyCompatible proto era => BlockSupportsMetrics (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node

Methods

isSelfIssued :: BlockConfig (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> WhetherSelfIssued

ShelleyCompatible proto era => BlockSupportsProtocol (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

Methods

validateView :: BlockConfig (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> ValidateView (BlockProtocol (ShelleyBlock proto era))

selectView :: BlockConfig (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> SelectView (BlockProtocol (ShelleyBlock proto era))

ConfigSupportsNode (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

Methods

getSystemStart :: BlockConfig (ShelleyBlock proto era) -> SystemStart

getNetworkMagic :: BlockConfig (ShelleyBlock proto era) -> NetworkMagic

HasHardForkHistory (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type HardForkIndices (ShelleyBlock proto era) :: [Type]

Methods

hardForkSummary :: LedgerConfig (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> Summary (HardForkIndices (ShelleyBlock proto era))

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) => NoHardForks (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

getEraParams :: TopLevelConfig (ShelleyBlock proto era) -> EraParams

toPartialLedgerConfig :: proxy (ShelleyBlock proto era) -> LedgerConfig (ShelleyBlock proto era) -> PartialLedgerConfig (ShelleyBlock proto era)

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) => SingleEraBlock (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

singleEraTransition :: PartialLedgerConfig (ShelleyBlock proto era) -> EraParams -> Bound -> LedgerState (ShelleyBlock proto era) -> Maybe EpochNo

singleEraInfo :: proxy (ShelleyBlock proto era) -> SingleEraInfo (ShelleyBlock proto era)

ShelleyCompatible proto era => CondenseConstraints (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Cardano.Condense

ShelleyCompatible proto era => HasPartialLedgerConfig (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type PartialLedgerConfig (ShelleyBlock proto era)

Methods

completeLedgerConfig :: proxy (ShelleyBlock proto era) -> EpochInfo (Except PastHorizonException) -> PartialLedgerConfig (ShelleyBlock proto era) -> LedgerConfig (ShelleyBlock proto era)

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) => SerialiseConstraintsHFC (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

ShelleyCompatible proto era => BasicEnvelopeValidation (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

expectedFirstBlockNo :: proxy (ShelleyBlock proto era) -> BlockNo

expectedNextBlockNo :: proxy (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> BlockNo -> BlockNo

minimumPossibleSlotNo :: Proxy (ShelleyBlock proto era) -> SlotNo

minimumNextSlotNo :: proxy (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> SlotNo -> SlotNo

ShelleyCompatible proto era => HasAnnTip (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type TipInfo (ShelleyBlock proto era)

Methods

getTipInfo :: Header (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era)

tipInfoHash :: proxy (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> HeaderHash (ShelleyBlock proto era)

ShelleyCompatible proto era => ValidateEnvelope (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type OtherHeaderEnvelopeError (ShelleyBlock proto era)

Methods

additionalEnvelopeChecks :: TopLevelConfig (ShelleyBlock proto era) -> LedgerView (BlockProtocol (ShelleyBlock proto era)) -> Header (ShelleyBlock proto era) -> Except (OtherHeaderEnvelopeError (ShelleyBlock proto era)) ()

ShelleyCompatible proto era => UpdateLedger (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyCompatible proto era => CommonProtocolParams (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyBasedEra era => InspectLedger (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Inspect

Associated Types

type LedgerWarning (ShelleyBlock proto era)

type LedgerUpdate (ShelleyBlock proto era)

Methods

inspectLedger :: TopLevelConfig (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> [LedgerEvent (ShelleyBlock proto era)]

(ShelleyCompatible proto era, ProtoCrypto proto ~ crypto) => QueryLedger (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

answerBlockQuery :: ExtLedgerCfg (ShelleyBlock proto era) -> BlockQuery (ShelleyBlock proto era) result -> ExtLedgerState (ShelleyBlock proto era) -> result

ShelleyBasedEra era => HasTxs (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

extractTxs :: ShelleyBlock proto era -> [GenTx (ShelleyBlock proto era)]

ShelleyCompatible proto era => LedgerSupportsMempool (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

txInvariant :: GenTx (ShelleyBlock proto era) -> Bool

applyTx :: LedgerConfig (ShelleyBlock proto era) -> WhetherToIntervene -> SlotNo -> GenTx (ShelleyBlock proto era) -> TickedLedgerState (ShelleyBlock proto era) -> Except (ApplyTxErr (ShelleyBlock proto era)) (TickedLedgerState (ShelleyBlock proto era), Validated (GenTx (ShelleyBlock proto era)))

reapplyTx :: LedgerConfig (ShelleyBlock proto era) -> SlotNo -> Validated (GenTx (ShelleyBlock proto era)) -> TickedLedgerState (ShelleyBlock proto era) -> Except (ApplyTxErr (ShelleyBlock proto era)) (TickedLedgerState (ShelleyBlock proto era))

txsMaxBytes :: TickedLedgerState (ShelleyBlock proto era) -> Word32

txInBlockSize :: GenTx (ShelleyBlock proto era) -> Word32

txForgetValidated :: Validated (GenTx (ShelleyBlock proto era)) -> GenTx (ShelleyBlock proto era)

c ~ EraCrypto era => LedgerSupportsPeerSelection (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.PeerSelection

Methods

getPeers :: LedgerState (ShelleyBlock proto era) -> [(PoolStake, NonEmpty StakePoolRelay)]

(ShelleyCompatible (Praos crypto) era, ShelleyCompatible (TPraos crypto) era, crypto ~ EraCrypto era, TranslateProto (TPraos crypto) (Praos crypto)) => LedgerSupportsProtocol (ShelleyBlock (Praos crypto) era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.SupportsProtocol

Methods

protocolLedgerView :: LedgerConfig (ShelleyBlock (Praos crypto) era) -> Ticked (LedgerState (ShelleyBlock (Praos crypto) era)) -> LedgerView (BlockProtocol (ShelleyBlock (Praos crypto) era))

ledgerViewForecastAt :: LedgerConfig (ShelleyBlock (Praos crypto) era) -> LedgerState (ShelleyBlock (Praos crypto) era) -> Forecast (LedgerView (BlockProtocol (ShelleyBlock (Praos crypto) era)))

(ShelleyCompatible (TPraos crypto) era, crypto ~ EraCrypto era) => LedgerSupportsProtocol (ShelleyBlock (TPraos crypto) era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.SupportsProtocol

Methods

protocolLedgerView :: LedgerConfig (ShelleyBlock (TPraos crypto) era) -> Ticked (LedgerState (ShelleyBlock (TPraos crypto) era)) -> LedgerView (BlockProtocol (ShelleyBlock (TPraos crypto) era))

ledgerViewForecastAt :: LedgerConfig (ShelleyBlock (TPraos crypto) era) -> LedgerState (ShelleyBlock (TPraos crypto) era) -> Forecast (LedgerView (BlockProtocol (ShelleyBlock (TPraos crypto) era)))

ShelleyCompatible p (AllegraEra c) => TxLimits (ShelleyBlock p (AllegraEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type TxMeasure (ShelleyBlock p (AllegraEra c))

ShelleyCompatible p (AlonzoEra c) => TxLimits (ShelleyBlock p (AlonzoEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type TxMeasure (ShelleyBlock p (AlonzoEra c))

ShelleyCompatible p (BabbageEra c) => TxLimits (ShelleyBlock p (BabbageEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type TxMeasure (ShelleyBlock p (BabbageEra c))

ShelleyCompatible p (ConwayEra c) => TxLimits (ShelleyBlock p (ConwayEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type TxMeasure (ShelleyBlock p (ConwayEra c))

ShelleyCompatible p (MaryEra c) => TxLimits (ShelleyBlock p (MaryEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type TxMeasure (ShelleyBlock p (MaryEra c))

ShelleyCompatible p (ShelleyEra c) => TxLimits (ShelleyBlock p (ShelleyEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type TxMeasure (ShelleyBlock p (ShelleyEra c))

ShelleyCompatible proto era => NodeInitStorage (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

Methods

nodeImmutableDbChunkInfo :: StorageConfig (ShelleyBlock proto era) -> ChunkInfo

nodeCheckIntegrity :: StorageConfig (ShelleyBlock proto era) -> ShelleyBlock proto era -> Bool

nodeInitChainDB :: IOLike m => StorageConfig (ShelleyBlock proto era) -> InitChainDB m (ShelleyBlock proto era) -> m ()

HasNetworkProtocolVersion (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

Associated Types

type BlockNodeToNodeVersion (ShelleyBlock proto era)

type BlockNodeToClientVersion (ShelleyBlock proto era)

SupportedNetworkProtocolVersion (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

Methods

supportedNodeToNodeVersions :: Proxy (ShelleyBlock proto era) -> Map NodeToNodeVersion (BlockNodeToNodeVersion (ShelleyBlock proto era))

supportedNodeToClientVersions :: Proxy (ShelleyBlock proto era) -> Map NodeToClientVersion (BlockNodeToClientVersion (ShelleyBlock proto era))

latestReleasedNodeVersion :: Proxy (ShelleyBlock proto era) -> (Maybe NodeToNodeVersion, Maybe NodeToClientVersion)

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) => SupportedNetworkProtocolVersion (ShelleyBlockHFC proto era)

Forward to the ShelleyBlock instance. Only supports HardForkNodeToNodeDisabled, which is compatible with nodes running with ShelleyBlock.

Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

supportedNodeToNodeVersions :: Proxy (ShelleyBlockHFC proto era) -> Map NodeToNodeVersion (BlockNodeToNodeVersion (ShelleyBlockHFC proto era))

supportedNodeToClientVersions :: Proxy (ShelleyBlockHFC proto era) -> Map NodeToClientVersion (BlockNodeToClientVersion (ShelleyBlockHFC proto era))

latestReleasedNodeVersion :: Proxy (ShelleyBlockHFC proto era) -> (Maybe NodeToNodeVersion, Maybe NodeToClientVersion)

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) => RunNode (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node

ShelleyCompatible proto era => SerialiseNodeToClientConstraints (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era => SerialiseNodeToNodeConstraints (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

estimateBlockSize :: Header (ShelleyBlock proto era) -> SizeInBytes

ShelleyCompatible proto era => SerialiseDiskConstraints (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era => HasBinaryBlockInfo (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

getBinaryBlockInfo :: ShelleyBlock proto era -> BinaryBlockInfo

ShelleyCompatible proto era => Condense (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

condense :: ShelleyBlock proto era -> String

SameDepIndex (NestedCtxt_ (ShelleyBlock proto era) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

sameDepIndex :: NestedCtxt_ (ShelleyBlock proto era) f a -> NestedCtxt_ (ShelleyBlock proto era) f b -> Maybe (a :~: b)

TrivialDependency (NestedCtxt_ (ShelleyBlock proto era) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f)

Methods

hasSingleIndex :: NestedCtxt_ (ShelleyBlock proto era) f a -> NestedCtxt_ (ShelleyBlock proto era) f b -> a :~: b

indexIsTrivial :: NestedCtxt_ (ShelleyBlock proto era) f (TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f))

ShelleyCompatible proto era => HasHeader (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeaderFields :: ShelleyBlock proto era -> HeaderFields (ShelleyBlock proto era)

ShelleyCompatible proto era => SerialiseNodeToClient (ShelleyBlock proto era) SlotNo 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> SlotNo -> Encoding

decodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> forall s. Decoder s SlotNo

ShelleyBasedEra era => SerialiseNodeToClient (ShelleyBlock proto era) (ApplyTxError era)
ApplyTxErr '(ShelleyBlock era)'
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> ApplyTxError era -> Encoding

decodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> forall s. Decoder s (ApplyTxError era)

ShelleyCompatible proto era => SerialiseNodeToClient (ShelleyBlock proto era) (GenTx (ShelleyBlock proto era))

Uses CBOR-in-CBOR in the To/FromCBOR instances to get the annotation.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> GenTx (ShelleyBlock proto era) -> Encoding

decodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> forall s. Decoder s (GenTx (ShelleyBlock proto era))

ShelleyCompatible proto era => SerialiseNodeToClient (ShelleyBlock proto era) (GenTxId (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> GenTxId (ShelleyBlock proto era) -> Encoding

decodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> forall s. Decoder s (GenTxId (ShelleyBlock proto era))

ShelleyCompatible proto era => SerialiseNodeToNode (ShelleyBlock proto era) (Header (ShelleyBlock proto era))

CBOR-in-CBOR to be compatible with the wrapped (Serialised) variant.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> Encoding

decodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> forall s. Decoder s (Header (ShelleyBlock proto era))

ShelleyCompatible proto era => SerialiseNodeToNode (ShelleyBlock proto era) (GenTx (ShelleyBlock proto era))

The To/FromCBOR instances defined in cardano-ledger use CBOR-in-CBOR to get the annotation.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> GenTx (ShelleyBlock proto era) -> Encoding

decodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> forall s. Decoder s (GenTx (ShelleyBlock proto era))

ShelleyCompatible proto era => SerialiseNodeToNode (ShelleyBlock proto era) (GenTxId (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> GenTxId (ShelleyBlock proto era) -> Encoding

decodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> forall s. Decoder s (GenTxId (ShelleyBlock proto era))

SerialiseNodeToNode (ShelleyBlock proto era) (SerialisedHeader (ShelleyBlock proto era))

We use CBOR-in-CBOR

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> SerialisedHeader (ShelleyBlock proto era) -> Encoding

decodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> forall s. Decoder s (SerialisedHeader (ShelleyBlock proto era))

ShelleyCompatible proto era => SerialiseResult (ShelleyBlock proto era) (BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeResult :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> BlockQuery (ShelleyBlock proto era) result -> result -> Encoding

decodeResult :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> BlockQuery (ShelleyBlock proto era) result -> forall s. Decoder s result

ShelleyCompatible proto era => DecodeDisk (ShelleyBlock proto era) (AnnTip (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDisk :: CodecConfig (ShelleyBlock proto era) -> forall s. Decoder s (AnnTip (ShelleyBlock proto era))

ShelleyCompatible proto era => DecodeDisk (ShelleyBlock proto era) (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDisk :: CodecConfig (ShelleyBlock proto era) -> forall s. Decoder s (LedgerState (ShelleyBlock proto era))

(ShelleyCompatible proto era, EraCrypto era ~ c, PraosCrypto c) => DecodeDisk (ShelleyBlock proto era) (PraosState c)
ChainDepState (BlockProtocol (ShelleyBlock era))
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDisk :: CodecConfig (ShelleyBlock proto era) -> forall s. Decoder s (PraosState c)

(ShelleyCompatible proto era, EraCrypto era ~ c, PraosCrypto c) => DecodeDisk (ShelleyBlock proto era) (TPraosState c)
ChainDepState (BlockProtocol (ShelleyBlock era))
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDisk :: CodecConfig (ShelleyBlock proto era) -> forall s. Decoder s (TPraosState c)

ShelleyCompatible proto era => EncodeDisk (ShelleyBlock proto era) (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDisk :: CodecConfig (ShelleyBlock proto era) -> Header (ShelleyBlock proto era) -> Encoding

ShelleyCompatible proto era => EncodeDisk (ShelleyBlock proto era) (AnnTip (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDisk :: CodecConfig (ShelleyBlock proto era) -> AnnTip (ShelleyBlock proto era) -> Encoding

ShelleyCompatible proto era => EncodeDisk (ShelleyBlock proto era) (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDisk :: CodecConfig (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> Encoding

(ShelleyCompatible proto era, EraCrypto era ~ c, PraosCrypto c) => EncodeDisk (ShelleyBlock proto era) (PraosState c) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDisk :: CodecConfig (ShelleyBlock proto era) -> PraosState c -> Encoding

(ShelleyCompatible proto era, EraCrypto era ~ c, PraosCrypto c) => EncodeDisk (ShelleyBlock proto era) (TPraosState c)
ChainDepState (BlockProtocol (ShelleyBlock era))
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDisk :: CodecConfig (ShelleyBlock proto era) -> TPraosState c -> Encoding

(Typeable era, Typeable proto) => ShowProxy (BlockQuery (ShelleyBlock proto era) :: Type -> Type) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showProxy :: Proxy (BlockQuery (ShelleyBlock proto era)) -> String

ShelleyCompatible proto era => SerialiseNodeToClient (ShelleyBlock proto era) (SomeSecond BlockQuery (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> SomeSecond BlockQuery (ShelleyBlock proto era) -> Encoding

decodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> forall s. Decoder s (SomeSecond BlockQuery (ShelleyBlock proto era))

ShelleyCompatible proto era => SerialiseNodeToClient (ShelleyBlock proto era) (ShelleyBlock proto era)

CBOR-in-CBOR for the annotation. This also makes it compatible with the wrapped (Serialised) variant.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> ShelleyBlock proto era -> Encoding

decodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> forall s. Decoder s (ShelleyBlock proto era)

SerialiseNodeToClient (ShelleyBlock proto era) (Serialised (ShelleyBlock proto era))

Serialised uses CBOR-in-CBOR by default.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> Serialised (ShelleyBlock proto era) -> Encoding

decodeNodeToClient :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToClientVersion (ShelleyBlock proto era) -> forall s. Decoder s (Serialised (ShelleyBlock proto era))

ShelleyCompatible proto era => SerialiseNodeToNode (ShelleyBlock proto era) (ShelleyBlock proto era)

CBOR-in-CBOR for the annotation. This also makes it compatible with the wrapped (Serialised) variant.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> ShelleyBlock proto era -> Encoding

decodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> forall s. Decoder s (ShelleyBlock proto era)

SerialiseNodeToNode (ShelleyBlock proto era) (Serialised (ShelleyBlock proto era))

Serialised uses CBOR-in-CBOR by default.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> Serialised (ShelleyBlock proto era) -> Encoding

decodeNodeToNode :: CodecConfig (ShelleyBlock proto era) -> BlockNodeToNodeVersion (ShelleyBlock proto era) -> forall s. Decoder s (Serialised (ShelleyBlock proto era))

ShelleyCompatible proto era => DecodeDisk (ShelleyBlock proto era) (ByteString -> Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDisk :: CodecConfig (ShelleyBlock proto era) -> forall s. Decoder s (ByteString -> Header (ShelleyBlock proto era))

ShelleyCompatible proto era => DecodeDisk (ShelleyBlock proto era) (ByteString -> ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDisk :: CodecConfig (ShelleyBlock proto era) -> forall s. Decoder s (ByteString -> ShelleyBlock proto era)

ShelleyCompatible proto era => EncodeDisk (ShelleyBlock proto era) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDisk :: CodecConfig (ShelleyBlock proto era) -> ShelleyBlock proto era -> Encoding

Show (NestedCtxt_ (ShelleyBlock proto era) f a) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrec :: Int -> NestedCtxt_ (ShelleyBlock proto era) f a -> ShowS Source #

show :: NestedCtxt_ (ShelleyBlock proto era) f a -> String Source #

showList :: [NestedCtxt_ (ShelleyBlock proto era) f a] -> ShowS Source #

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) => SerialiseHFC '[ShelleyBlock proto era]

Use the default implementations. This means the serialisation of blocks includes an era wrapper. Each block should do this from the start to be prepared for future hard forks without having to do any bit twiddling.

Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

encodeDiskHfcBlock :: CodecConfig (HardForkBlock '[ShelleyBlock proto era]) -> HardForkBlock '[ShelleyBlock proto era] -> Encoding

decodeDiskHfcBlock :: CodecConfig (HardForkBlock '[ShelleyBlock proto era]) -> forall s. Decoder s (ByteString -> HardForkBlock '[ShelleyBlock proto era])

reconstructHfcPrefixLen :: proxy (Header (HardForkBlock '[ShelleyBlock proto era])) -> PrefixLen

reconstructHfcNestedCtxt :: proxy (Header (HardForkBlock '[ShelleyBlock proto era])) -> ShortByteString -> SizeInBytes -> SomeSecond (NestedCtxt Header) (HardForkBlock '[ShelleyBlock proto era])

getHfcBinaryBlockInfo :: HardForkBlock '[ShelleyBlock proto era] -> BinaryBlockInfo

estimateHfcBlockSize :: Header (HardForkBlock '[ShelleyBlock proto era]) -> SizeInBytes

type HeaderHash (ShelleyBlock proto era :: Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type HeaderHash (ShelleyBlock proto era :: Type) = ShelleyHash (ProtoCrypto proto)
type TranslationError era (LedgerState :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (LedgerState :.: ShelleyBlock proto) = Void
type TranslationError era (GenTx :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (GenTx :.: ShelleyBlock proto) = TranslationError era WrapTx
type TranslationError era (WrapValidatedGenTx :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (WrapValidatedGenTx :.: ShelleyBlock proto) = TranslationError era WrapTx
type Rep (BlockConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type Rep (BlockConfig (ShelleyBlock proto era)) = D1 ('MetaData "BlockConfig" "Ouroboros.Consensus.Shelley.Ledger.Config" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyConfig" 'PrefixI 'True) ((S1 ('MetaSel ('Just "shelleyProtocolVersion") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ProtVer) :*: S1 ('MetaSel ('Just "shelleySystemStart") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SystemStart)) :*: (S1 ('MetaSel ('Just "shelleyNetworkMagic") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 NetworkMagic) :*: S1 ('MetaSel ('Just "shelleyBlockIssuerVKeys") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'BlockIssuer (EraCrypto era)) (VKey 'BlockIssuer (EraCrypto era)))))))
type Rep (CodecConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type Rep (CodecConfig (ShelleyBlock proto era)) = D1 ('MetaData "CodecConfig" "Ouroboros.Consensus.Shelley.Ledger.Config" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyCodecConfig" 'PrefixI 'False) (U1 :: Type -> Type))
type Rep (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type Rep (Header (ShelleyBlock proto era)) = D1 ('MetaData "Header" "Ouroboros.Consensus.Shelley.Ledger.Block" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyHeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyHeaderRaw") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShelleyProtocolHeader proto)) :*: S1 ('MetaSel ('Just "shelleyHeaderHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShelleyHash (ProtoCrypto proto)))))
type Rep (StorageConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type Rep (StorageConfig (ShelleyBlock proto era)) = D1 ('MetaData "StorageConfig" "Ouroboros.Consensus.Shelley.Ledger.Config" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyStorageConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyStorageConfigSlotsPerKESPeriod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "shelleyStorageConfigSecurityParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SecurityParam)))
type Rep (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type Rep (Validated (GenTx (ShelleyBlock proto era))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.Shelley.Ledger.Mempool" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyValidatedTx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TxId (EraCrypto era))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Validated (Tx era)))))
type Rep (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (LedgerState (ShelleyBlock proto era)) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyLedgerTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (ShelleyTip proto era))) :*: (S1 ('MetaSel ('Just "shelleyLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NewEpochState era)) :*: S1 ('MetaSel ('Just "shelleyLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShelleyTransition))))
type Rep (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type Rep (GenTx (ShelleyBlock proto era)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.Shelley.Ledger.Mempool" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyTx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TxId (EraCrypto era))) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Tx era))))
type Rep (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "TickedShelleyLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "untickedShelleyLedgerTip") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin (ShelleyTip proto era))) :*: (S1 ('MetaSel ('Just "tickedShelleyLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ShelleyTransition) :*: S1 ('MetaSel ('Just "tickedShelleyLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (NewEpochState era)))))
data Validated (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

data Validated (GenTx (ShelleyBlock proto era)) = ShelleyValidatedTx !(TxId (EraCrypto era)) !(Validated (Tx era))
type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerEvent era
type LedgerCfg (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerCfg (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerConfig era
type LedgerErr (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerErr (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerError era
newtype TxId (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

newtype TxId (GenTx (ShelleyBlock proto era)) = ShelleyTxId (TxId (EraCrypto era))
data ProtocolParams (CardanoBlock c) Source #

Parameters needed to run Cardano.

Instance details

Defined in Ouroboros.Consensus.Cardano.Node

type Signed (Header (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

type Signed (Header (ShelleyBlock proto era)) = Signed (ShelleyProtocolHeader proto)
data Ticked (LedgerState (ShelleyBlock proto era)) Source #

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data BlockConfig (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

data BlockConfig (ShelleyBlock proto era) = ShelleyConfig {}
type BlockProtocol (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

type BlockProtocol (ShelleyBlock proto era) = proto
data CodecConfig (ShelleyBlock proto era) Source #

No particular codec configuration is needed for Shelley

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

data Header (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

data StorageConfig (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type CannotForge (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

type CannotForge (ShelleyBlock proto era) = CannotForgeError proto
type ForgeStateInfo (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

type ForgeStateInfo (ShelleyBlock proto era) = KESInfo
type ForgeStateUpdateError (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

type ForgeStateUpdateError (ShelleyBlock proto era) = KESEvolutionError
data NestedCtxt_ (ShelleyBlock proto era) f a Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

data NestedCtxt_ (ShelleyBlock proto era) f a where
type HardForkIndices (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type HardForkIndices (ShelleyBlock proto era) = '[ShelleyBlock proto era]
type PartialLedgerConfig (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type PartialLedgerConfig (ShelleyBlock proto era) = ShelleyPartialLedgerConfig era
type OtherHeaderEnvelopeError (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type OtherHeaderEnvelopeError (ShelleyBlock proto era) = EnvelopeCheckError proto
type TipInfo (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type TipInfo (ShelleyBlock proto era) = HeaderHash (ShelleyBlock proto era)
data LedgerState (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerUpdate (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Inspect

type LedgerUpdate (ShelleyBlock proto era) = ShelleyLedgerUpdate era
type LedgerWarning (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Inspect

type LedgerWarning (ShelleyBlock proto era) = Void
data BlockQuery (ShelleyBlock proto era) a Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

data BlockQuery (ShelleyBlock proto era) a where
type ApplyTxErr (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type ApplyTxErr (ShelleyBlock proto era) = ApplyTxError era
data GenTx (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

data GenTx (ShelleyBlock proto era) = ShelleyTx !(TxId (EraCrypto era)) !(Tx era)
type TxMeasure (ShelleyBlock p (AllegraEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p (AllegraEra c)) = ByteSize
type TxMeasure (ShelleyBlock p (AlonzoEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p (AlonzoEra c)) = AlonzoMeasure
type TxMeasure (ShelleyBlock p (BabbageEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p (BabbageEra c)) = AlonzoMeasure
type TxMeasure (ShelleyBlock p (ConwayEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p (ConwayEra c)) = AlonzoMeasure
type TxMeasure (ShelleyBlock p (MaryEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p (MaryEra c)) = ByteSize
type TxMeasure (ShelleyBlock p (ShelleyEra c)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p (ShelleyEra c)) = ByteSize
type BlockNodeToClientVersion (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

type BlockNodeToClientVersion (ShelleyBlock proto era) = ShelleyNodeToClientVersion
type BlockNodeToNodeVersion (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

type BlockNodeToNodeVersion (ShelleyBlock proto era) = ShelleyNodeToNodeVersion
data ProtocolParams (ShelleyBlock (Praos c) (BabbageEra c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Praos

data ProtocolParams (ShelleyBlock (Praos c) (ConwayEra c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Praos

data ProtocolParams (ShelleyBlock (TPraos c) (AllegraEra c)) Source #

Parameters needed to run Allegra

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.TPraos

data ProtocolParams (ShelleyBlock (TPraos c) (AlonzoEra c)) Source #

Parameters needed to run Alonzo

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.TPraos

data ProtocolParams (ShelleyBlock (TPraos c) (MaryEra c)) Source #

Parameters needed to run Mary

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.TPraos

data ProtocolParams (ShelleyBlock (TPraos c) (ShelleyEra c)) Source #

Parameters needed to run Shelley

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.TPraos

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) = f (ShelleyBlock proto era)

newtype ShelleyHash crypto Source #

Constructors

ShelleyHash 

Fields

Instances

Instances details
Generic (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Associated Types

type Rep (ShelleyHash crypto) :: Type -> Type Source #

Methods

from :: ShelleyHash crypto -> Rep (ShelleyHash crypto) x Source #

to :: Rep (ShelleyHash crypto) x -> ShelleyHash crypto Source #

Show (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

showsPrec :: Int -> ShelleyHash crypto -> ShowS Source #

show :: ShelleyHash crypto -> String Source #

showList :: [ShelleyHash crypto] -> ShowS Source #

Crypto crypto => FromCBOR (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

fromCBOR :: Decoder s (ShelleyHash crypto)

label :: Proxy (ShelleyHash crypto) -> Text

Crypto crypto => ToCBOR (ShelleyHash crypto) Source # 
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

Eq (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

(==) :: ShelleyHash crypto -> ShelleyHash crypto -> Bool Source #

(/=) :: ShelleyHash crypto -> ShelleyHash crypto -> Bool Source #

Ord (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

compare :: ShelleyHash crypto -> ShelleyHash crypto -> Ordering Source #

(<) :: ShelleyHash crypto -> ShelleyHash crypto -> Bool Source #

(<=) :: ShelleyHash crypto -> ShelleyHash crypto -> Bool Source #

(>) :: ShelleyHash crypto -> ShelleyHash crypto -> Bool Source #

(>=) :: ShelleyHash crypto -> ShelleyHash crypto -> Bool Source #

max :: ShelleyHash crypto -> ShelleyHash crypto -> ShelleyHash crypto Source #

min :: ShelleyHash crypto -> ShelleyHash crypto -> ShelleyHash crypto Source #

NoThunks (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

noThunks :: Context -> ShelleyHash crypto -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ShelleyHash crypto -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (ShelleyHash crypto) -> String

Condense (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

condense :: ShelleyHash crypto -> String

Crypto crypto => Serialise (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

encode :: ShelleyHash crypto -> Encoding

decode :: Decoder s (ShelleyHash crypto)

encodeList :: [ShelleyHash crypto] -> Encoding

decodeList :: Decoder s [ShelleyHash crypto]

type Rep (ShelleyHash crypto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

type Rep (ShelleyHash crypto) = D1 ('MetaData "ShelleyHash" "Ouroboros.Consensus.Shelley.Protocol.Abstract" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'True) (C1 ('MetaCons "ShelleyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unShelleyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash crypto EraIndependentBlockHeader))))

Shelley Compatibility

class (ShelleyBasedEra era, ShelleyProtocol proto, Eq (ShelleyProtocolHeader proto), Show (ShelleyProtocolHeader proto), NoThunks (ShelleyProtocolHeader proto), EncCBOR (ShelleyProtocolHeader proto), DecCBOR (Annotator (ShelleyProtocolHeader proto)), Show (CannotForgeError proto), SelectView proto ~ PraosChainSelectView (EraCrypto era), SignedHeader (ShelleyProtocolHeader proto), DecodeDisk (ShelleyBlock proto era) (ChainDepState proto), EncodeDisk (ShelleyBlock proto era) (ChainDepState proto), EraCrypto era ~ ProtoCrypto proto, HasPartialConsensusConfig proto, DecCBOR (PState era), FromCBOR (LegacyPParams era), ToCBOR (LegacyPParams era)) => ShelleyCompatible proto era Source #

Instances

Instances details
PraosCrypto c => ShelleyCompatible (Praos c) (BabbageEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

PraosCrypto c => ShelleyCompatible (Praos c) (ConwayEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

(PraosCrypto c, Signable (DSIGN c) (Hash (HASH c) EraIndependentTxBody)) => ShelleyCompatible (TPraos c) (AllegraEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

(PraosCrypto c, Signable (DSIGN c) (Hash (HASH c) EraIndependentTxBody)) => ShelleyCompatible (TPraos c) (AlonzoEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

(PraosCrypto c, PraosCrypto c) => ShelleyCompatible (TPraos c) (BabbageEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

(PraosCrypto c, PraosCrypto c) => ShelleyCompatible (TPraos c) (ConwayEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

(PraosCrypto c, Signable (DSIGN c) (Hash (HASH c) EraIndependentTxBody)) => ShelleyCompatible (TPraos c) (MaryEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

(PraosCrypto c, Signable (DSIGN c) (Hash (HASH c) EraIndependentTxBody)) => ShelleyCompatible (TPraos c) (ShelleyEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.HFEras

mkShelleyBlock :: ShelleyCompatible proto era => Block (ShelleyProtocolHeader proto) era -> ShelleyBlock proto era Source #

Serialisation

decodeShelleyBlock :: forall proto era. ShelleyCompatible proto era => forall s. Decoder s (ByteString -> ShelleyBlock proto era) Source #

decodeShelleyHeader :: forall proto era. ShelleyCompatible proto era => forall s. Decoder s (ByteString -> Header (ShelleyBlock proto era)) Source #

encodeShelleyBlock :: forall proto era. ShelleyCompatible proto era => ShelleyBlock proto era -> Encoding Source #

encodeShelleyHeader :: forall proto era. ShelleyCompatible proto era => Header (ShelleyBlock proto era) -> Encoding Source #

shelleyBinaryBlockInfo :: forall proto era. ShelleyCompatible proto era => ShelleyBlock proto era -> BinaryBlockInfo Source #

Conversion

fromShelleyPrevHash :: EraCrypto era ~ ProtoCrypto proto => PrevHash (EraCrypto era) -> ChainHash (ShelleyBlock proto era) Source #

From cardano-ledger-specs to ouroboros-consensus

toShelleyPrevHash :: EraCrypto era ~ ProtoCrypto proto => ChainHash (Header (ShelleyBlock proto era)) -> PrevHash (EraCrypto era) Source #

From ouroboros-consensus to cardano-ledger-specs