ouroboros-consensus-cardano-0.25.0.1: The instantation of the Ouroboros consensus layer used by Cardano
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.Shelley.Ledger.Block

Synopsis

Documentation

class HasHeader (Header blk) ⇒ GetHeader blk where Source #

Methods

getHeader ∷ blk → Header blk Source #

blockMatchesHeaderHeader blk → blk → Bool Source #

Check whether the header is the header of the block.

For example, by checking whether the hash of the body stored in the header matches that of the block.

headerIsEBBHeader blk → Maybe EpochNo Source #

When the given header is the header of an Epoch Boundary Block, returns its epoch number.

data family Header blk Source #

Instances

Instances details
GetHeader1 Header 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

Methods

getHeader1Header blk → Header blk Source #

Inject Header 
Instance details

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

Methods

inject ∷ ∀ x (xs ∷ [Type]). (CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ InjectionIndex xs x → Header x → Header (HardForkBlock xs) Source #

Isomorphic Header 
Instance details

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

Methods

projectNoHardForks blk ⇒ Header (HardForkBlock '[blk]) → Header blk Source #

injectNoHardForks blk ⇒ Header blk → Header (HardForkBlock '[blk]) Source #

HasNestedContent Header ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Serialisation

ReconstructNestedCtxt Header ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

SerialiseNodeToNode ByronBlock (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

StandardHash blk ⇒ StandardHash (Header blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

ShowProxy (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

(Typeable era, Typeable proto) ⇒ ShowProxy (Header (ShelleyBlock proto era) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showProxyProxy (Header (ShelleyBlock proto era)) → String Source #

HasNestedContent Header m ⇒ HasNestedContent Header (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ReconstructNestedCtxt Header m ⇒ ReconstructNestedCtxt Header (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ShelleyBasedEra era ⇒ ReconstructNestedCtxt Header (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

(Typeable m, Typeable a) ⇒ ShowProxy (DualHeader m a ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (DualHeader m a) → String Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

decCBORDecoder s (Annotator (Header (ShelleyBlock proto era))) Source #

dropCBORProxy (Annotator (Header (ShelleyBlock proto era))) → Decoder s () Source #

labelProxy (Annotator (Header (ShelleyBlock proto era))) → Text Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

encCBORHeader (ShelleyBlock proto era) → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (Header (ShelleyBlock proto era)) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [Header (ShelleyBlock proto era)] → Size Source #

Generic (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

Associated Types

type Rep (Header ByronBlock) 
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.25.0.1-inplace" '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))))
Generic (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type Rep (Header (ShelleyBlock proto era)) 
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.25.0.1-inplace" '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)))

Methods

fromHeader (ShelleyBlock proto era) → Rep (Header (ShelleyBlock proto era)) x #

toRep (Header (ShelleyBlock proto era)) x → Header (ShelleyBlock proto era) #

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

showsPrecIntHeader (ShelleyBlock proto era) → ShowS #

showHeader (ShelleyBlock proto era) → String #

showList ∷ [Header (ShelleyBlock proto era)] → ShowS #

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 #

(/=)Header (ShelleyBlock proto era) → Header (ShelleyBlock proto era) → Bool #

NoThunks (Header (DualBlock m a)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

NoThunks (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

SignedHeader (ShelleyProtocolHeader proto) ⇒ SignedHeader (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

Methods

headerSignedHeader (ShelleyBlock proto era) → Signed (Header (ShelleyBlock proto era)) Source #

Condense (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

condenseHeader (ShelleyBlock proto era) → String Source #

HasHeader (Header ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Block

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeaderFieldsHeader (ShelleyBlock proto era) → HeaderFields (Header (ShelleyBlock proto era)) Source #

DecodeDiskDep (NestedCtxt Header) ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

DecodeDiskDepIx (NestedCtxt Header) ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

EncodeDiskDep (NestedCtxt Header) ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

EncodeDiskDepIx (NestedCtxt Header) ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

ShelleyCompatible proto era ⇒ DecodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskDepCodecConfig (ShelleyBlock proto era) → NestedCtxt Header (ShelleyBlock proto era) a → ∀ s. Decoder s (ByteString → a) Source #

ShelleyBasedEra era ⇒ DecodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

EncodeDiskDep (NestedCtxt Header) m ⇒ EncodeDiskDep (NestedCtxt Header) (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

encodeDiskDepCodecConfig (DualBlock m a) → NestedCtxt Header (DualBlock m a) a0 → a0 → Encoding Source #

ShelleyCompatible proto era ⇒ EncodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskDepCodecConfig (ShelleyBlock proto era) → NestedCtxt Header (ShelleyBlock proto era) a → a → Encoding Source #

EncodeDiskDepIx (NestedCtxt Header) m ⇒ EncodeDiskDepIx (NestedCtxt Header) (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ShelleyBasedEra era ⇒ EncodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Show (Header m) ⇒ Show (DualHeader m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntDualHeader m a → ShowS #

showDualHeader m a → String #

showList ∷ [DualHeader m a] → ShowS #

Bridge m a ⇒ HasHeader (DualHeader m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

ShelleyCompatible proto era ⇒ SerialiseNodeToNode (ShelleyBlock proto era) (Header (ShelleyBlock proto era)) Source #

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

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ EncodeDisk (ShelleyBlock proto era) (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskCodecConfig (ShelleyBlock proto era) → Header (ShelleyBlock proto era) → Encoding Source #

ShelleyCompatible proto era ⇒ DecodeDisk (ShelleyBlock proto era) (ByteStringHeader (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskCodecConfig (ShelleyBlock proto era) → ∀ s. Decoder s (ByteStringHeader (ShelleyBlock proto era)) Source #

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

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.25.0.1-inplace" '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.25.0.1-inplace" '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)))
type BlockProtocol (Header blk) 
Instance details

Defined in Ouroboros.Consensus.Block.Abstract

newtype Header (DisableDiffusionPipelining blk) 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (SelectViewDiffusionPipelining blk) 
Instance details

Defined in Ouroboros.Consensus.Block.SupportsDiffusionPipelining

newtype Header (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

newtype Header (DualBlock m a) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data Header (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

class (ShelleyCompatible (BlockProtocol blk) (ShelleyBlockLedgerEra blk), blk ~ ShelleyBlock (BlockProtocol blk) (ShelleyBlockLedgerEra blk)) ⇒ IsShelleyBlock blk Source #

Instances

Instances details
(proto ~ BlockProtocol (ShelleyBlock proto era), ShelleyCompatible proto era) ⇒ IsShelleyBlock (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

data family NestedCtxt_ blk ∷ (TypeType) → TypeType Source #

Context identifying what kind of block we have

In almost all places we will use NestedCtxt rather than NestedCtxt_.

Instances

Instances details
SameDepIndex (NestedCtxt_ m f) ⇒ SameDepIndex (NestedCtxt_ (DualBlock m a) f ∷ TypeType) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

sameDepIndexNestedCtxt_ (DualBlock m a) f a0 → NestedCtxt_ (DualBlock m a) f b → Maybe (a0 :~: b) Source #

SameDepIndex (NestedCtxt_ ByronBlock f ∷ TypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Serialisation

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

sameDepIndexNestedCtxt_ (ShelleyBlock proto era) f a → NestedCtxt_ (ShelleyBlock proto era) f b → Maybe (a :~: b) Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

hasSingleIndexNestedCtxt_ (ShelleyBlock proto era) f a → NestedCtxt_ (ShelleyBlock proto era) f b → a :~: b Source #

indexIsTrivialNestedCtxt_ (ShelleyBlock proto era) f (TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) ∷ Type) Source #

Show (NestedCtxt_ m f x) ⇒ Show (NestedCtxt_ (DualBlock m a) f x) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntNestedCtxt_ (DualBlock m a) f x → ShowS #

showNestedCtxt_ (DualBlock m a) f x → String #

showList ∷ [NestedCtxt_ (DualBlock m a) f x] → ShowS #

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

showsPrecIntNestedCtxt_ (ShelleyBlock proto era) f a → ShowS #

showNestedCtxt_ (ShelleyBlock proto era) f a → String #

showList ∷ [NestedCtxt_ (ShelleyBlock proto era) f a] → ShowS #

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f ∷ TypeType) = f (ShelleyBlock proto era)
data NestedCtxt_ (HardForkBlock xs) a b 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Block

data NestedCtxt_ (HardForkBlock xs) a b where
newtype NestedCtxt_ (DualBlock m a) f x 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype NestedCtxt_ (DualBlock m a) f x 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

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)), Eq (PredicateFailure (EraRule "BBODY" era)), Show (PredicateFailure (EraRule "BBODY" era)), NoThunks (PredicateFailure (EraRule "BBODY" era)), NoThunks (TranslationContext era), ToCBOR (TranslationContext era), FromCBOR (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/IntersectMBO/ouroboros-network/issues/2890

Minimal complete definition

applyShelleyBasedTx, getConwayEraGovDict

Instances

Instances details
ShelleyBasedEra AllegraEra Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

ShelleyBasedEra AlonzoEra Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

ShelleyBasedEra BabbageEra Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

ShelleyBasedEra ConwayEra Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

ShelleyBasedEra MaryEra Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

ShelleyBasedEra ShelleyEra Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

data ShelleyBlock proto era Source #

Shelley-based block type.

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

Instances

Instances details
SameDepIndex2 (BlockQuery (ShelleyBlock proto era) ∷ QueryFootprintTypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

sameDepIndex2 ∷ ∀ (x ∷ QueryFootprint) a (y ∷ QueryFootprint) b. BlockQuery (ShelleyBlock proto era) x a → BlockQuery (ShelleyBlock proto era) y b → Maybe ('(x, a) :~: '(y, b)) Source #

(Typeable era, Typeable proto) ⇒ ShowProxy (Header (ShelleyBlock proto era) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showProxyProxy (Header (ShelleyBlock proto era)) → String Source #

(Typeable era, Typeable proto) ⇒ ShowProxy (Validated (GenTx (ShelleyBlock proto era)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxyProxy (Validated (GenTx (ShelleyBlock proto era))) → String Source #

(Typeable era, Typeable proto) ⇒ ShowProxy (GenTx (ShelleyBlock proto era) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxyProxy (GenTx (ShelleyBlock proto era)) → String Source #

(Typeable era, Typeable proto) ⇒ ShowProxy (TxId (GenTx (ShelleyBlock proto era)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showProxyProxy (TxId (GenTx (ShelleyBlock proto era))) → String Source #

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

nestDepPair (NestedCtxt f (ShelleyBlock proto era)) → f (ShelleyBlock proto era) Source #

ShelleyBasedEra era ⇒ ReconstructNestedCtxt Header (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

sameDepIndexNestedCtxt_ (ShelleyBlock proto era) f a → NestedCtxt_ (ShelleyBlock proto era) f b → Maybe (a :~: b) Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

hasSingleIndexNestedCtxt_ (ShelleyBlock proto era) f a → NestedCtxt_ (ShelleyBlock proto era) f b → a :~: b Source #

indexIsTrivialNestedCtxt_ (ShelleyBlock proto era) f (TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f) ∷ Type) Source #

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

showProxyProxy (ShelleyBlock proto era) → String Source #

ShelleyCompatible proto era ⇒ SerialiseBlockQueryResult (ShelleyBlock proto era) BlockQuery Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) fp result → result → Encoding Source #

decodeBlockQueryResult ∷ ∀ (fp ∷ QueryFootprint) result. CodecConfig (ShelleyBlock proto era) → BlockNodeToClientVersion (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) fp result → ∀ s. Decoder s result Source #

(ShelleyBasedEra era, TranslateEra era WrapTx) ⇒ TranslateEra era (GenTx :.: ShelleyBlock proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

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

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

(ShelleyBasedEra era, TranslateEra era WrapTx) ⇒ TranslateEra era (WrapValidatedGenTx :.: ShelleyBlock proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

(ShelleyBasedEra era, ShelleyBasedEra (PreviousEra era), TranslateEra era (ShelleyTip proto), TranslateEra era NewEpochState, TranslationError era NewEpochState ~ Void, CanMapMK mk, CanMapKeysMK mk) ⇒ TranslateEra era (Flip LedgerState mk :.: ShelleyBlock proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (Flip LedgerState mk :.: ShelleyBlock proto) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

ShelleyCompatible proto era ⇒ FromCBOR (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

fromCBORDecoder s (GenTx (ShelleyBlock proto era)) Source #

labelProxy (GenTx (ShelleyBlock proto era)) → Text Source #

ShelleyCompatible proto era ⇒ ToCBOR (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

toCBORGenTx (ShelleyBlock proto era) → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (GenTx (ShelleyBlock proto era)) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [GenTx (ShelleyBlock proto era)] → Size Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

decCBORDecoder s (Annotator (Header (ShelleyBlock proto era))) Source #

dropCBORProxy (Annotator (Header (ShelleyBlock proto era))) → Decoder s () Source #

labelProxy (Annotator (Header (ShelleyBlock proto era))) → Text Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

decCBORDecoder s (Annotator (ShelleyBlock proto era)) Source #

dropCBORProxy (Annotator (ShelleyBlock proto era)) → Decoder s () Source #

labelProxy (Annotator (ShelleyBlock proto era)) → Text Source #

(Typeable era, Typeable proto, Crypto (ProtoCrypto proto)) ⇒ DecCBOR (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

decCBORDecoder s (TxId (GenTx (ShelleyBlock proto era))) Source #

dropCBORProxy (TxId (GenTx (ShelleyBlock proto era))) → Decoder s () Source #

labelProxy (TxId (GenTx (ShelleyBlock proto era))) → Text Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

encCBORHeader (ShelleyBlock proto era) → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (Header (ShelleyBlock proto era)) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [Header (ShelleyBlock proto era)] → Size Source #

(Typeable era, Typeable proto, Crypto (ProtoCrypto proto)) ⇒ EncCBOR (TxId (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

encCBORTxId (GenTx (ShelleyBlock proto era)) → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (TxId (GenTx (ShelleyBlock proto era))) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [TxId (GenTx (ShelleyBlock proto era))] → Size Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (BlockConfig (ShelleyBlock proto era)) 
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.25.0.1-inplace" '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) (VKey 'BlockIssuer))) :*: S1 ('MetaSel ('Just "shelleyVRFTiebreakerFlavor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VRFTiebreakerFlavor)))))

Methods

fromBlockConfig (ShelleyBlock proto era) → Rep (BlockConfig (ShelleyBlock proto era)) x #

toRep (BlockConfig (ShelleyBlock proto era)) x → BlockConfig (ShelleyBlock proto era) #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (CodecConfig (ShelleyBlock proto era)) 
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.25.0.1-inplace" 'False) (C1 ('MetaCons "ShelleyCodecConfig" 'PrefixI 'False) (U1TypeType))

Methods

fromCodecConfig (ShelleyBlock proto era) → Rep (CodecConfig (ShelleyBlock proto era)) x #

toRep (CodecConfig (ShelleyBlock proto era)) x → CodecConfig (ShelleyBlock proto era) #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type Rep (Header (ShelleyBlock proto era)) 
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.25.0.1-inplace" '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)))

Methods

fromHeader (ShelleyBlock proto era) → Rep (Header (ShelleyBlock proto era)) x #

toRep (Header (ShelleyBlock proto era)) x → Header (ShelleyBlock proto era) #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Associated Types

type Rep (StorageConfig (ShelleyBlock proto era)) 
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.25.0.1-inplace" 'False) (C1 ('MetaCons "ShelleyStorageConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyStorageConfigSlotsPerKESPeriod") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Word64) :*: S1 ('MetaSel ('Just "shelleyStorageConfigSecurityParam") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SecurityParam)))

Methods

fromStorageConfig (ShelleyBlock proto era) → Rep (StorageConfig (ShelleyBlock proto era)) x #

toRep (StorageConfig (ShelleyBlock proto era)) x → StorageConfig (ShelleyBlock proto era) #

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))) 
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.25.0.1-inplace" 'False) (C1 ('MetaCons "ShelleyValidatedTx" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Validated (Tx era)))))

Methods

fromValidated (GenTx (ShelleyBlock proto era)) → Rep (Validated (GenTx (ShelleyBlock proto era))) x #

toRep (Validated (GenTx (ShelleyBlock proto era))) x → Validated (GenTx (ShelleyBlock proto era)) #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Associated Types

type Rep (GenTx (ShelleyBlock proto era)) 
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.25.0.1-inplace" 'False) (C1 ('MetaCons "ShelleyTx" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Tx era))))

Methods

fromGenTx (ShelleyBlock proto era) → Rep (GenTx (ShelleyBlock proto era)) x #

toRep (GenTx (ShelleyBlock proto era)) x → GenTx (ShelleyBlock proto era) #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

Methods

showsPrecIntBlockConfig (ShelleyBlock proto era) → ShowS #

showBlockConfig (ShelleyBlock proto era) → String #

showList ∷ [BlockConfig (ShelleyBlock proto era)] → ShowS #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrecIntHeader (ShelleyBlock proto era) → ShowS #

showHeader (ShelleyBlock proto era) → String #

showList ∷ [Header (ShelleyBlock proto era)] → ShowS #

Show (CanonicalTxIn (CardanoEras c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

Show (CanonicalTxIn '[ShelleyBlock proto era]) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

showsPrecIntCanonicalTxIn '[ShelleyBlock proto era] → ShowS #

showCanonicalTxIn '[ShelleyBlock proto era] → String #

showList ∷ [CanonicalTxIn '[ShelleyBlock proto era]] → ShowS #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntValidated (GenTx (ShelleyBlock proto era)) → ShowS #

showValidated (GenTx (ShelleyBlock proto era)) → String #

showList ∷ [Validated (GenTx (ShelleyBlock proto era))] → ShowS #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntGenTx (ShelleyBlock proto era) → ShowS #

showGenTx (ShelleyBlock proto era) → String #

showList ∷ [GenTx (ShelleyBlock proto era)] → ShowS #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

showsPrecIntGenTxId (ShelleyBlock proto era) → ShowS #

showGenTxId (ShelleyBlock proto era) → String #

showList ∷ [GenTxId (ShelleyBlock proto era)] → ShowS #

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 #

(/=)Header (ShelleyBlock proto era) → Header (ShelleyBlock proto era) → Bool #

Eq (CanonicalTxIn (CardanoEras c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

Eq (CanonicalTxIn '[ShelleyBlock proto era]) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

(==)CanonicalTxIn '[ShelleyBlock proto era] → CanonicalTxIn '[ShelleyBlock proto era] → Bool #

(/=)CanonicalTxIn '[ShelleyBlock proto era] → CanonicalTxIn '[ShelleyBlock proto era] → Bool #

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 #

(/=)Validated (GenTx (ShelleyBlock proto era)) → Validated (GenTx (ShelleyBlock proto era)) → Bool #

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 #

(/=)GenTx (ShelleyBlock proto era) → GenTx (ShelleyBlock proto era) → Bool #

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 #

(/=)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool #

Ord (CanonicalTxIn (CardanoEras c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

Ord (CanonicalTxIn '[ShelleyBlock proto era]) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

compareCanonicalTxIn '[ShelleyBlock proto era] → CanonicalTxIn '[ShelleyBlock proto era] → Ordering #

(<)CanonicalTxIn '[ShelleyBlock proto era] → CanonicalTxIn '[ShelleyBlock proto era] → Bool #

(<=)CanonicalTxIn '[ShelleyBlock proto era] → CanonicalTxIn '[ShelleyBlock proto era] → Bool #

(>)CanonicalTxIn '[ShelleyBlock proto era] → CanonicalTxIn '[ShelleyBlock proto era] → Bool #

(>=)CanonicalTxIn '[ShelleyBlock proto era] → CanonicalTxIn '[ShelleyBlock proto era] → Bool #

maxCanonicalTxIn '[ShelleyBlock proto era] → CanonicalTxIn '[ShelleyBlock proto era] → CanonicalTxIn '[ShelleyBlock proto era] #

minCanonicalTxIn '[ShelleyBlock proto era] → CanonicalTxIn '[ShelleyBlock proto era] → CanonicalTxIn '[ShelleyBlock proto era] #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

compareTxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Ordering #

(<)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool #

(<=)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool #

(>)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool #

(>=)TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → Bool #

maxTxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) #

minTxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) → TxId (GenTx (ShelleyBlock proto era)) #

CardanoHardForkConstraints c ⇒ MemPack (CanonicalTxIn (CardanoEras c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

MemPack (CanonicalTxIn '[ShelleyBlock proto era]) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

ShelleyBasedEra era ⇒ NoThunks (BlockConfig (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

NoThunks (CanonicalTxIn (CardanoEras c)) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

NoThunks (CanonicalTxIn '[ShelleyBlock proto era]) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

ShelleyBasedEra era ⇒ NoThunks (Validated (GenTx (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

ShelleyBasedEra era ⇒ NoThunks (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

noThunksContextTxId (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) Source #

wNoThunksContextTxId (GenTx (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (TxId (GenTx (ShelleyBlock proto era))) → String Source #

CardanoHardForkConstraints c ⇒ CanHardFork (CardanoEras c) Source #

When performing era translations, two eras have special behaviours on the ledger tables:

  • Byron to Shelley: as Byron has no tables, the whole UTxO set is computed as insertions, note that it uses valuesAsDiffs
  • Shelley to Allegra: some special addresses (the so called AVVM addresses), were deleted in this transition, which influenced things like the calculation of later rewards. In this transition, we consume the shelleyToAllegraAVVMsToDelete as deletions in the ledger tables.
Instance details

Defined in Ouroboros.Consensus.Cardano.CanHardFork

CardanoHardForkConstraints c ⇒ CondenseConstraints (CardanoBlock c) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Condense

CardanoHardForkConstraints c ⇒ HasCanonicalTxIn (CardanoEras c) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

Associated Types

newtype CanonicalTxIn (CardanoEras c) 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

CardanoHardForkConstraints c ⇒ HasHardForkTxOut (CardanoEras c) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

Associated Types

type HardForkTxOut (CardanoEras c) 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

CardanoHardForkConstraints c ⇒ BlockSupportsHFLedgerQuery (CardanoEras c) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.QueryHF

CardanoHardForkConstraints c ⇒ SerialiseHFC (CardanoEras c) Source #

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/IntersectMBO/ouroboros-network/pull/1175#issuecomment-558147194

Instance details

Defined in Ouroboros.Consensus.Cardano.Node

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTip ∷ ∀ (mk ∷ MapKind). LedgerState (ShelleyBlock proto era) mk → Point (LedgerState (ShelleyBlock proto era)) Source #

ShelleyBasedEra era ⇒ IsLedger (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type LedgerErr (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyBasedEra era ⇒ ConvertRawTxId (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

ShelleyBasedEra era ⇒ HasTxId (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

txIdGenTx (ShelleyBlock proto era) → TxId (GenTx (ShelleyBlock proto era)) Source #

ShelleyBasedEra era ⇒ CanStowLedgerTables (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyBasedEra era ⇒ HasLedgerTables (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (ShelleyBlock proto era) mk → LedgerTables (LedgerState (ShelleyBlock proto era)) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ LedgerState (ShelleyBlock proto era) any → LedgerTables (LedgerState (ShelleyBlock proto era)) mk → LedgerState (ShelleyBlock proto era) mk Source #

CardanoHardForkConstraints c ⇒ SerializeTablesWithHint (LedgerState (HardForkBlock (CardanoEras c))) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

ShelleyCompatible proto era ⇒ SerializeTablesWithHint (LedgerState (HardForkBlock '[ShelleyBlock proto era])) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

ShelleyCompatible proto era ⇒ SerializeTablesWithHint (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

CardanoHardForkConstraints c ⇒ SupportedNetworkProtocolVersion (CardanoBlock c) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Node

SignedHeader (ShelleyProtocolHeader proto) ⇒ SignedHeader (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

Methods

headerSignedHeader (ShelleyBlock proto era) → Signed (Header (ShelleyBlock proto era)) Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

upgradeTables ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). LedgerState (ShelleyBlock proto era) mk1 → LedgerState (ShelleyBlock proto era) mk2 → LedgerTables (LedgerState (ShelleyBlock proto era)) ValuesMKLedgerTables (LedgerState (ShelleyBlock proto era)) ValuesMK Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

condenseHeader (ShelleyBlock proto era) → String Source #

ShelleyBasedEra era ⇒ Condense (GenTx (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

condenseGenTx (ShelleyBlock proto era) → String Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

condenseGenTxId (ShelleyBlock proto era) → String Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeaderFieldsHeader (ShelleyBlock proto era) → HeaderFields (Header (ShelleyBlock proto era)) Source #

ShelleyCompatible proto era ⇒ ApplyBlock (LedgerState (ShelleyBlock proto era)) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyCompatible proto era ⇒ DecodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskDepCodecConfig (ShelleyBlock proto era) → NestedCtxt Header (ShelleyBlock proto era) a → ∀ s. Decoder s (ByteString → a) Source #

ShelleyBasedEra era ⇒ DecodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ EncodeDiskDep (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskDepCodecConfig (ShelleyBlock proto era) → NestedCtxt Header (ShelleyBlock proto era) a → a → Encoding Source #

ShelleyBasedEra era ⇒ EncodeDiskDepIx (NestedCtxt Header) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ EncCBOR (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

encCBORShelleyBlock proto era → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (ShelleyBlock proto era) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [ShelleyBlock proto era] → Size Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (LedgerState (ShelleyBlock proto era) mk) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (LedgerState (ShelleyBlock proto era) mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.25.0.1-inplace" '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) :*: S1 ('MetaSel ('Just "shelleyLedgerTables") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerTables (LedgerState (ShelleyBlock proto era)) mk)))))

Methods

fromLedgerState (ShelleyBlock proto era) mk → Rep (LedgerState (ShelleyBlock proto era) mk) x #

toRep (LedgerState (ShelleyBlock proto era) mk) x → LedgerState (ShelleyBlock proto era) mk #

(ShelleyBasedEra era, ShowMK mk) ⇒ Show (LedgerState (ShelleyBlock proto era) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

showsPrecIntLedgerState (ShelleyBlock proto era) mk → ShowS #

showLedgerState (ShelleyBlock proto era) mk → String #

showList ∷ [LedgerState (ShelleyBlock proto era) mk] → ShowS #

ShelleyCompatible proto era ⇒ Show (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrecIntShelleyBlock proto era → ShowS #

showShelleyBlock proto era → String #

showList ∷ [ShelleyBlock proto era] → ShowS #

(ShelleyBasedEra era, EqMK mk) ⇒ Eq (LedgerState (ShelleyBlock proto era) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

(==)LedgerState (ShelleyBlock proto era) mk → LedgerState (ShelleyBlock proto era) mk → Bool #

(/=)LedgerState (ShelleyBlock proto era) mk → LedgerState (ShelleyBlock proto era) mk → Bool #

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 #

(/=)ShelleyBlock proto era → ShelleyBlock proto era → Bool #

(ShelleyBasedEra era, NoThunksMK mk) ⇒ NoThunks (LedgerState (ShelleyBlock proto era) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

fromRawHash ∷ proxy (ShelleyBlock proto era) → ByteStringHeaderHash (ShelleyBlock proto era) Source #

toShortRawHash ∷ proxy (ShelleyBlock proto era) → HeaderHash (ShelleyBlock proto era) → ShortByteString Source #

fromShortRawHash ∷ proxy (ShelleyBlock proto era) → ShortByteStringHeaderHash (ShelleyBlock proto era) Source #

hashSize ∷ proxy (ShelleyBlock proto era) → Word32 Source #

ShelleyCompatible proto era ⇒ GetHeader (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeaderShelleyBlock proto era → Header (ShelleyBlock proto era) Source #

blockMatchesHeaderHeader (ShelleyBlock proto era) → ShelleyBlock proto era → Bool Source #

headerIsEBBHeader (ShelleyBlock proto era) → Maybe EpochNo Source #

ShelleyCompatible proto era ⇒ GetPrevHash (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

headerPrevHashHeader (ShelleyBlock proto era) → ChainHash (ShelleyBlock proto era) Source #

(ShelleyCompatible proto era, BlockSupportsProtocol (ShelleyBlock proto era)) ⇒ BlockSupportsDiffusionPipelining (ShelleyBlock proto era) Source #

A header can be pipelined iff no trap header with the same block number and by the same issuer was pipelined before. See HotIdentity for what exactly we use for the issuer identity.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.DiffusionPipelining

ShelleyCompatible proto era ⇒ BlockSupportsMetrics (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node

ShelleyCompatible proto era ⇒ BlockSupportsProtocol (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

ConsensusProtocol proto ⇒ BlockSupportsSanityCheck (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node

ConfigSupportsNode (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

HasHardForkHistory (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type HardForkIndices (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type HardForkIndices (ShelleyBlock proto era) = '[ShelleyBlock proto era]

Methods

hardForkSummary ∷ ∀ (mk ∷ MapKind). LedgerConfig (ShelleyBlock proto era) → LedgerState (ShelleyBlock proto era) mk → Summary (HardForkIndices (ShelleyBlock proto era)) Source #

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) ⇒ ImmutableEraParams (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era), TxLimits (ShelleyBlock proto era), Crypto (ProtoCrypto proto)) ⇒ NoHardForks (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

toPartialLedgerConfig ∷ proxy (ShelleyBlock proto era) → LedgerConfig (ShelleyBlock proto era) → PartialLedgerConfig (ShelleyBlock proto era) Source #

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era), TxLimits (ShelleyBlock proto era), Crypto (ProtoCrypto proto)) ⇒ SingleEraBlock (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

singleEraTransition ∷ ∀ (mk ∷ MapKind). PartialLedgerConfig (ShelleyBlock proto era) → EraParamsBoundLedgerState (ShelleyBlock proto era) mk → Maybe EpochNo Source #

singleEraInfo ∷ proxy (ShelleyBlock proto era) → SingleEraInfo (ShelleyBlock proto era) Source #

ShelleyCompatible proto era ⇒ CondenseConstraints (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Condense

ShelleyCompatible proto era ⇒ HasPartialLedgerConfig (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type PartialLedgerConfig (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era), TxLimits (ShelleyBlock proto era), Crypto (ProtoCrypto proto)) ⇒ SerialiseConstraintsHFC (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

ShelleyCompatible proto era ⇒ BasicEnvelopeValidation (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

expectedFirstBlockNo ∷ proxy (ShelleyBlock proto era) → BlockNo Source #

expectedNextBlockNo ∷ proxy (ShelleyBlock proto era) → TipInfo (ShelleyBlock proto era) → TipInfo (ShelleyBlock proto era) → BlockNoBlockNo Source #

minimumPossibleSlotNoProxy (ShelleyBlock proto era) → SlotNo Source #

minimumNextSlotNo ∷ proxy (ShelleyBlock proto era) → TipInfo (ShelleyBlock proto era) → TipInfo (ShelleyBlock proto era) → SlotNoSlotNo Source #

ShelleyCompatible proto era ⇒ HasAnnTip (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Associated Types

type TipInfo (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type TipInfo (ShelleyBlock proto era) = HeaderHash (ShelleyBlock proto era)

Methods

getTipInfoHeader (ShelleyBlock proto era) → TipInfo (ShelleyBlock proto era) Source #

tipInfoHash ∷ proxy (ShelleyBlock proto era) → TipInfo (ShelleyBlock proto era) → HeaderHash (ShelleyBlock proto era) Source #

ShelleyCompatible proto era ⇒ ValidateEnvelope (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type OtherHeaderEnvelopeError (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyCompatible proto era ⇒ UpdateLedger (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (ShelleyBlock proto era)) mk → Point (Ticked (LedgerState (ShelleyBlock proto era))) Source #

ShelleyCompatible proto era ⇒ CommonProtocolParams (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

maxHeaderSize ∷ ∀ (mk ∷ MapKind). LedgerState (ShelleyBlock proto era) mk → Word32 Source #

maxTxSize ∷ ∀ (mk ∷ MapKind). LedgerState (ShelleyBlock proto era) mk → Word32 Source #

ShelleyBasedEra era ⇒ InspectLedger (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Inspect

Associated Types

type LedgerWarning (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Inspect

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Inspect

Methods

inspectLedger ∷ ∀ (mk1 ∷ MapKind) (mk2 ∷ MapKind). TopLevelConfig (ShelleyBlock proto era) → LedgerState (ShelleyBlock proto era) mk1 → LedgerState (ShelleyBlock proto era) mk2 → [LedgerEvent (ShelleyBlock proto era)] Source #

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era), ProtoCrypto proto ~ crypto, Crypto crypto) ⇒ BlockSupportsLedgerQuery (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

answerPureBlockQueryExtLedgerCfg (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) 'QFNoTables result → ExtLedgerState (ShelleyBlock proto era) EmptyMK → result Source #

answerBlockQueryLookupMonadSTM m ⇒ ExtLedgerCfg (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) 'QFLookupTables result → ReadOnlyForker' m (ShelleyBlock proto era) → m result Source #

answerBlockQueryTraverseMonadSTM m ⇒ ExtLedgerCfg (ShelleyBlock proto era) → BlockQuery (ShelleyBlock proto era) 'QFTraverseTables result → ReadOnlyForker' m (ShelleyBlock proto era) → m result Source #

blockQueryIsSupportedOnVersion ∷ ∀ (fp ∷ QueryFootprint) result. BlockQuery (ShelleyBlock proto era) fp result → BlockNodeToClientVersion (ShelleyBlock proto era) → Bool Source #

ShelleyBasedEra era ⇒ HasTxs (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

extractTxsShelleyBlock proto era → [GenTx (ShelleyBlock proto era)] Source #

(ShelleyCompatible proto era, TxLimits (ShelleyBlock proto era)) ⇒ LedgerSupportsMempool (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

Methods

txInvariantGenTx (ShelleyBlock proto era) → Bool Source #

applyTxLedgerConfig (ShelleyBlock proto era) → WhetherToInterveneSlotNoGenTx (ShelleyBlock proto era) → TickedLedgerState (ShelleyBlock proto era) ValuesMKExcept (ApplyTxErr (ShelleyBlock proto era)) (TickedLedgerState (ShelleyBlock proto era) DiffMK, Validated (GenTx (ShelleyBlock proto era))) Source #

reapplyTxComputeDiffsLedgerConfig (ShelleyBlock proto era) → SlotNoValidated (GenTx (ShelleyBlock proto era)) → TickedLedgerState (ShelleyBlock proto era) ValuesMKExcept (ApplyTxErr (ShelleyBlock proto era)) (TickedLedgerState (ShelleyBlock proto era) TrackingMK) Source #

reapplyTxsComputeDiffsLedgerConfig (ShelleyBlock proto era) → SlotNo → [(Validated (GenTx (ShelleyBlock proto era)), extra)] → TickedLedgerState (ShelleyBlock proto era) ValuesMKReapplyTxsResult extra (ShelleyBlock proto era) Source #

txForgetValidatedValidated (GenTx (ShelleyBlock proto era)) → GenTx (ShelleyBlock proto era) Source #

getTransactionKeySetsGenTx (ShelleyBlock proto era) → LedgerTables (LedgerState (ShelleyBlock proto era)) KeysMK Source #

prependMempoolDiffsTickedLedgerState (ShelleyBlock proto era) DiffMKTickedLedgerState (ShelleyBlock proto era) DiffMKTickedLedgerState (ShelleyBlock proto era) DiffMK Source #

applyMempoolDiffsLedgerTables (LedgerState (ShelleyBlock proto era)) ValuesMKLedgerTables (LedgerState (ShelleyBlock proto era)) KeysMKTickedLedgerState (ShelleyBlock proto era) DiffMKTickedLedgerState (ShelleyBlock proto era) ValuesMK Source #

ShelleyCompatible p AllegraEraTxLimits (ShelleyBlock p AllegraEra) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

ShelleyCompatible p AlonzoEraTxLimits (ShelleyBlock p AlonzoEra) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

ShelleyCompatible p BabbageEraTxLimits (ShelleyBlock p BabbageEra) Source #

We anachronistically use ConwayMeasure in Babbage.

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

ShelleyCompatible p ConwayEraTxLimits (ShelleyBlock p ConwayEra) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

ShelleyCompatible p MaryEraTxLimits (ShelleyBlock p MaryEra) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

ShelleyCompatible p ShelleyEraTxLimits (ShelleyBlock p ShelleyEra) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

EraCertState era ⇒ LedgerSupportsPeerSelection (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.PeerSelection

Methods

getPeers ∷ ∀ (mk ∷ MapKind). LedgerState (ShelleyBlock proto era) mk → [(PoolStake, NonEmpty StakePoolRelay)] Source #

(ShelleyCompatible (Praos crypto) era, ShelleyCompatible (TPraos crypto) era) ⇒ LedgerSupportsProtocol (ShelleyBlock (Praos crypto) era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.SupportsProtocol

Methods

protocolLedgerView ∷ ∀ (mk ∷ MapKind). LedgerConfig (ShelleyBlock (Praos crypto) era) → Ticked (LedgerState (ShelleyBlock (Praos crypto) era)) mk → LedgerView (BlockProtocol (ShelleyBlock (Praos crypto) era)) Source #

ledgerViewForecastAt ∷ ∀ (mk ∷ MapKind). HasCallStackLedgerConfig (ShelleyBlock (Praos crypto) era) → LedgerState (ShelleyBlock (Praos crypto) era) mk → Forecast (LedgerView (BlockProtocol (ShelleyBlock (Praos crypto) era))) Source #

ShelleyCompatible (TPraos crypto) era ⇒ LedgerSupportsProtocol (ShelleyBlock (TPraos crypto) era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.SupportsProtocol

Methods

protocolLedgerView ∷ ∀ (mk ∷ MapKind). LedgerConfig (ShelleyBlock (TPraos crypto) era) → Ticked (LedgerState (ShelleyBlock (TPraos crypto) era)) mk → LedgerView (BlockProtocol (ShelleyBlock (TPraos crypto) era)) Source #

ledgerViewForecastAt ∷ ∀ (mk ∷ MapKind). HasCallStackLedgerConfig (ShelleyBlock (TPraos crypto) era) → LedgerState (ShelleyBlock (TPraos crypto) era) mk → Forecast (LedgerView (BlockProtocol (ShelleyBlock (TPraos crypto) era))) Source #

ShelleyBasedEra era ⇒ CanStowLedgerTables (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyBasedEra era ⇒ HasLedgerTables (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (ShelleyBlock proto era)) mk → LedgerTables (Ticked (LedgerState (ShelleyBlock proto era))) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (LedgerState (ShelleyBlock proto era)) any → LedgerTables (Ticked (LedgerState (ShelleyBlock proto era))) mk → Ticked (LedgerState (ShelleyBlock proto era)) mk Source #

ShelleyCompatible proto era ⇒ NodeInitStorage (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

HasNetworkProtocolVersion (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

SupportedNetworkProtocolVersion (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era), TxLimits (ShelleyBlock proto era), Crypto (ProtoCrypto proto)) ⇒ SupportedNetworkProtocolVersion (ShelleyBlockHFC proto era) Source #

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

Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era), BlockSupportsSanityCheck (ShelleyBlock proto era), TxLimits (ShelleyBlock proto era), SerialiseNodeToClientConstraints (ShelleyBlock proto era), Crypto (ProtoCrypto proto)) ⇒ RunNode (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node

(NoHardForks (ShelleyBlock proto era), ShelleyCompatible proto era) ⇒ SerialiseNodeToClientConstraints (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ SerialiseNodeToNodeConstraints (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ SerialiseDiskConstraints (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ HasBinaryBlockInfo (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ Condense (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

condenseShelleyBlock proto era → String Source #

(proto ~ BlockProtocol (ShelleyBlock proto era), ShelleyCompatible proto era) ⇒ IsShelleyBlock (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

ShelleyCompatible proto era ⇒ HasHeader (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

getHeaderFieldsShelleyBlock proto era → HeaderFields (ShelleyBlock proto era) Source #

ShelleyCompatible proto era ⇒ ShowQuery (BlockQuery (ShelleyBlock proto era) fp) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showResultBlockQuery (ShelleyBlock proto era) fp result → result → String Source #

ShelleyCompatible proto era ⇒ SerialiseNodeToClient (ShelleyBlock proto era) SlotNo Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ DecodeDisk (ShelleyBlock proto era) PraosState Source #
ChainDepState (BlockProtocol (ShelleyBlock era))
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskCodecConfig (ShelleyBlock proto era) → ∀ s. Decoder s PraosState Source #

ShelleyCompatible proto era ⇒ DecodeDisk (ShelleyBlock proto era) TPraosState Source #
ChainDepState (BlockProtocol (ShelleyBlock era))
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskCodecConfig (ShelleyBlock proto era) → ∀ s. Decoder s TPraosState Source #

ShelleyCompatible proto era ⇒ EncodeDisk (ShelleyBlock proto era) PraosState Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ EncodeDisk (ShelleyBlock proto era) TPraosState Source #
ChainDepState (BlockProtocol (ShelleyBlock era))
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

(txout ~ TxOut era, MemPack txout) ⇒ IndexedMemPack (LedgerState (HardForkBlock '[ShelleyBlock proto era]) EmptyMK) txout Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

(txout ~ TxOut era, MemPack txout) ⇒ IndexedMemPack (LedgerState (ShelleyBlock proto era) EmptyMK) txout Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyBasedEra era ⇒ SerialiseNodeToClient (ShelleyBlock proto era) (ApplyTxError era) Source #
ApplyTxErr '(ShelleyBlock era)'
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era)) ⇒ SerialiseNodeToClient (ShelleyBlock proto era) (SomeBlockQuery (BlockQuery (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ SerialiseNodeToClient (ShelleyBlock proto era) (GenTx (ShelleyBlock proto era)) Source #

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

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ SerialiseNodeToClient (ShelleyBlock proto era) (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

(NoHardForks (ShelleyBlock proto era), ShelleyCompatible proto era) ⇒ SerialiseNodeToClient (ShelleyBlock proto era) (ShelleyLedgerConfig era) Source #

This instance uses the invariant that the EpochInfo in a ShelleyLedgerConfig is fixed i.e. has a constant EpochSize and SlotLength. This is not true in the case of the HFC in a ShelleyPartialLedgerConfig, but that is handled correctly in the respective SerialiseNodeToClient instance for ShelleyPartialLedgerConfig.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyBasedEra era ⇒ SerialiseNodeToClient (ShelleyBlock proto era) (ShelleyPartialLedgerConfig era) Source #

This instance uses the invariant that the EpochInfo in a ShelleyPartialLedgerConfig is always just a dummy value.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ SerialiseNodeToNode (ShelleyBlock proto era) (Header (ShelleyBlock proto era)) Source #

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

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ SerialiseNodeToNode (ShelleyBlock proto era) (GenTx (ShelleyBlock proto era)) Source #

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

ShelleyCompatible proto era ⇒ SerialiseNodeToNode (ShelleyBlock proto era) (GenTxId (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

SerialiseNodeToNode (ShelleyBlock proto era) (SerialisedHeader (ShelleyBlock proto era)) Source #

We use CBOR-in-CBOR

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ DecodeDisk (ShelleyBlock proto era) (AnnTip (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskCodecConfig (ShelleyBlock proto era) → ∀ s. Decoder s (AnnTip (ShelleyBlock proto era)) Source #

ShelleyCompatible proto era ⇒ EncodeDisk (ShelleyBlock proto era) (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskCodecConfig (ShelleyBlock proto era) → Header (ShelleyBlock proto era) → Encoding Source #

ShelleyCompatible proto era ⇒ EncodeDisk (ShelleyBlock proto era) (AnnTip (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskCodecConfig (ShelleyBlock proto era) → AnnTip (ShelleyBlock proto era) → Encoding Source #

CardanoHardForkConstraints c ⇒ IndexedMemPack (LedgerState (HardForkBlock (CardanoEras c)) EmptyMK) (CardanoTxOut c) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

(Typeable era, Typeable proto) ⇒ ShowProxy (BlockQuery (ShelleyBlock proto era) ∷ QueryFootprintTypeType) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showProxyProxy (BlockQuery (ShelleyBlock proto era)) → String Source #

ShelleyCompatible proto era ⇒ SerialiseNodeToClient (ShelleyBlock proto era) (ShelleyBlock proto era) Source #

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

SerialiseNodeToClient (ShelleyBlock proto era) (Serialised (ShelleyBlock proto era)) Source #

Serialised uses CBOR-in-CBOR by default.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ SerialiseNodeToNode (ShelleyBlock proto era) (ShelleyBlock proto era) Source #

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

SerialiseNodeToNode (ShelleyBlock proto era) (Serialised (ShelleyBlock proto era)) Source #

Serialised uses CBOR-in-CBOR by default.

Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ DecodeDisk (ShelleyBlock proto era) (LedgerState (ShelleyBlock proto era) EmptyMK) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskCodecConfig (ShelleyBlock proto era) → ∀ s. Decoder s (LedgerState (ShelleyBlock proto era) EmptyMK) Source #

ShelleyCompatible proto era ⇒ DecodeDisk (ShelleyBlock proto era) (ByteStringHeader (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskCodecConfig (ShelleyBlock proto era) → ∀ s. Decoder s (ByteStringHeader (ShelleyBlock proto era)) Source #

ShelleyCompatible proto era ⇒ DecodeDisk (ShelleyBlock proto era) (ByteStringShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDiskCodecConfig (ShelleyBlock proto era) → ∀ s. Decoder s (ByteStringShelleyBlock proto era) Source #

ShelleyCompatible proto era ⇒ EncodeDisk (ShelleyBlock proto era) (LedgerState (ShelleyBlock proto era) EmptyMK) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

ShelleyCompatible proto era ⇒ EncodeDisk (ShelleyBlock proto era) (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDiskCodecConfig (ShelleyBlock proto era) → ShelleyBlock proto era → Encoding Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState (ShelleyBlock proto era)) mk) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (Ticked (LedgerState (ShelleyBlock proto era)) mk) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.25.0.1-inplace" '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)) :*: S1 ('MetaSel ('Just "tickedShelleyLedgerTables") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerTables (LedgerState (ShelleyBlock proto era)) mk)))))

Methods

fromTicked (LedgerState (ShelleyBlock proto era)) mk → Rep (Ticked (LedgerState (ShelleyBlock proto era)) mk) x #

toRep (Ticked (LedgerState (ShelleyBlock proto era)) mk) x → Ticked (LedgerState (ShelleyBlock proto era)) mk #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

Methods

showsPrecIntNestedCtxt_ (ShelleyBlock proto era) f a → ShowS #

showNestedCtxt_ (ShelleyBlock proto era) f a → String #

showList ∷ [NestedCtxt_ (ShelleyBlock proto era) f a] → ShowS #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

showsPrecIntBlockQuery (ShelleyBlock proto era) fp result → ShowS #

showBlockQuery (ShelleyBlock proto era) fp result → String #

showList ∷ [BlockQuery (ShelleyBlock proto era) fp result] → ShowS #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

Methods

(==)BlockQuery (ShelleyBlock proto era) fp result → BlockQuery (ShelleyBlock proto era) fp result → Bool #

(/=)BlockQuery (ShelleyBlock proto era) fp result → BlockQuery (ShelleyBlock proto era) fp result → Bool #

(ShelleyCompatible proto era, ShelleyBasedEra era) ⇒ HasCanonicalTxIn '[ShelleyBlock proto era] Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

newtype CanonicalTxIn '[ShelleyBlock proto era] 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

injectCanonicalTxInIndex '[ShelleyBlock proto era] x → TxIn (LedgerState x) → CanonicalTxIn '[ShelleyBlock proto era] Source #

ejectCanonicalTxInIndex '[ShelleyBlock proto era] x → CanonicalTxIn '[ShelleyBlock proto era] → TxIn (LedgerState x) Source #

ShelleyCompatible proto era ⇒ HasHardForkTxOut '[ShelleyBlock proto era] Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type HardForkTxOut '[ShelleyBlock proto era] 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type HardForkTxOut '[ShelleyBlock proto era] = TxOut era
(ShelleyCompatible proto era, ShelleyBasedEra era, TxOut (LedgerState (ShelleyBlock proto era)) ~ TxOut era, HasHardForkTxOut '[ShelleyBlock proto era]) ⇒ BlockSupportsHFLedgerQuery '[ShelleyBlock proto era] Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

(ShelleyCompatible proto era, LedgerSupportsProtocol (ShelleyBlock proto era), TxLimits (ShelleyBlock proto era), Crypto (ProtoCrypto proto)) ⇒ SerialiseHFC '[ShelleyBlock proto era] Source #

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type TrivialIndex (NestedCtxt_ (ShelleyBlock proto era) f ∷ TypeType) = f (ShelleyBlock proto era)
type HeaderHash (ShelleyBlock proto era ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Block

type HeaderHash (ShelleyBlock proto era ∷ Type) = ShelleyHash
type TranslationError era (GenTx :.: ShelleyBlock proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (WrapValidatedGenTx :.: ShelleyBlock proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (Flip LedgerState mk :.: ShelleyBlock proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

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.25.0.1-inplace" '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) (VKey 'BlockIssuer))) :*: S1 ('MetaSel ('Just "shelleyVRFTiebreakerFlavor") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 VRFTiebreakerFlavor)))))
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.25.0.1-inplace" 'False) (C1 ('MetaCons "ShelleyCodecConfig" 'PrefixI 'False) (U1TypeType))
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.25.0.1-inplace" '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)))
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.25.0.1-inplace" '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.25.0.1-inplace" 'False) (C1 ('MetaCons "ShelleyValidatedTx" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Validated (Tx era)))))
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.25.0.1-inplace" 'False) (C1 ('MetaCons "ShelleyTx" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TxId) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Tx era))))
type HardForkTxMeasure (CardanoEras c) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.CanHardFork

newtype CanonicalTxIn (CardanoEras c) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

type HardForkTxOut (CardanoEras c) Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerCfg (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerErr (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

newtype TxId (GenTx (ShelleyBlock proto era)) = ShelleyTxId TxId
type TxIn (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type TxIn (LedgerState (ShelleyBlock proto era)) = TxIn
type TxOut (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type TxOut (LedgerState (ShelleyBlock proto era)) = TxOut era
type Signed (Header (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Protocol

type Rep (LedgerState (ShelleyBlock proto era) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (LedgerState (ShelleyBlock proto era) mk) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.25.0.1-inplace" '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) :*: S1 ('MetaSel ('Just "shelleyLedgerTables") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerTables (LedgerState (ShelleyBlock proto era)) mk)))))
data BlockConfig (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Config

type BlockProtocol (ShelleyBlock proto era) Source # 
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) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

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

Defined in Ouroboros.Consensus.Shelley.Node.Common

type ForgeStateUpdateError (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Common

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 TentativeHeaderState (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.DiffusionPipelining

type TentativeHeaderView (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.DiffusionPipelining

type HardForkIndices (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type OtherHeaderEnvelopeError (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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) mk Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerUpdate (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Inspect

type LedgerWarning (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Inspect

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Query

data BlockQuery (ShelleyBlock proto era) fp result where
type ApplyTxErr (ShelleyBlock proto era) Source # 
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 !(Tx era)
type TxMeasure (ShelleyBlock p AllegraEra) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p AlonzoEra) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p BabbageEra) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p ConwayEra) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p MaryEra) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type TxMeasure (ShelleyBlock p ShelleyEra) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Mempool

type BlockNodeToClientVersion (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

type BlockNodeToNodeVersion (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.NetworkProtocolVersion

data Ticked (LedgerState (ShelleyBlock proto era) ∷ MapKindType) (mk ∷ MapKind) Source #

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (Ticked (LedgerState (ShelleyBlock proto era)) mk) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (Ticked (LedgerState (ShelleyBlock proto era)) mk) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.25.0.1-inplace" '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)) :*: S1 ('MetaSel ('Just "tickedShelleyLedgerTables") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerTables (LedgerState (ShelleyBlock proto era)) mk)))))
newtype CanonicalTxIn '[ShelleyBlock proto era] Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type HardForkTxOut '[ShelleyBlock proto era] Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type HardForkTxOut '[ShelleyBlock proto era] = TxOut era

type family ShelleyBlockLedgerEra blk where ... Source #

Equations

ShelleyBlockLedgerEra (ShelleyBlock proto era) = era 

newtype ShelleyHash Source #

Instances

Instances details
FromCBOR ShelleyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

ToCBOR ShelleyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Methods

toCBORShelleyHashEncoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy ShelleyHashSize Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [ShelleyHash] → Size Source #

Generic ShelleyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Associated Types

type Rep ShelleyHash 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

type Rep ShelleyHash = D1 ('MetaData "ShelleyHash" "Ouroboros.Consensus.Shelley.Protocol.Abstract" "ouroboros-consensus-cardano-0.25.0.1-inplace" 'True) (C1 ('MetaCons "ShelleyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unShelleyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash HASH EraIndependentBlockHeader))))
Show ShelleyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Eq ShelleyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Ord ShelleyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

NoThunks ShelleyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Condense ShelleyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

Serialise ShelleyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

type Rep ShelleyHash Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Protocol.Abstract

type Rep ShelleyHash = D1 ('MetaData "ShelleyHash" "Ouroboros.Consensus.Shelley.Protocol.Abstract" "ouroboros-consensus-cardano-0.25.0.1-inplace" 'True) (C1 ('MetaCons "ShelleyHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unShelleyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash HASH 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 (ProtoCrypto proto), SignedHeader (ShelleyProtocolHeader proto), DecodeDisk (ShelleyBlock proto era) (ChainDepState proto), EncodeDisk (ShelleyBlock proto era) (ChainDepState proto), HasPartialConsensusConfig proto, DecCBOR (PState era), Crypto (ProtoCrypto proto)) ⇒ ShelleyCompatible proto era Source #

Serialisation

decodeShelleyBlockShelleyCompatible proto era ⇒ ∀ s. Decoder s (ByteStringShelleyBlock proto era) Source #

decodeShelleyHeaderShelleyCompatible proto era ⇒ ∀ s. Decoder s (ByteStringHeader (ShelleyBlock proto era)) Source #

Conversion

fromShelleyPrevHashPrevHashChainHash (ShelleyBlock proto era) Source #

From cardano-ledger-specs to ouroboros-consensus

toShelleyPrevHashChainHash (Header (ShelleyBlock proto era)) → PrevHash Source #

From ouroboros-consensus to cardano-ledger-specs