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

Ouroboros.Consensus.Shelley.Ledger.Ledger

Synopsis

Documentation

data family LedgerState blk Source #

Ledger state associated with a block

This is the Consensus notion of a ledger state. Each block type is associated with one of the Ledger types for the ledger state. Virtually every concept in this codebase revolves around this type, or the referenced blk. Whenever we use the type variable l, we intend to denote that the expected instantiation is either a LedgerState or some wrapper over it (like the ExtLedgerState).

The main operations we can do with a LedgerState are ticking (defined in IsLedger), and applying a block (defined in ApplyBlock).

Instances

Instances details
Inject LedgerState 
Instance details

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

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ Exactly xs BoundIndex xs x → LedgerState x → LedgerState (HardForkBlock xs) Source #

DecodeDisk ByronBlock (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

EncodeDisk ByronBlock (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

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

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (LedgerState :.: ShelleyBlock proto) Source #

Generic (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type Rep (LedgerState ByronBlock) ∷ TypeType #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (LedgerState (ShelleyBlock proto era)) ∷ TypeType #

Methods

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

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

Generic (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState ByronBlock)) ∷ TypeType #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) ∷ TypeType #

Methods

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

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

CanHardFork xs ⇒ Show (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Show (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

showsPrecIntLedgerState (ShelleyBlock proto era) → ShowS #

showLedgerState (ShelleyBlock proto era) → String #

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

CanHardFork xs ⇒ Eq (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Eq (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

CanHardFork xs ⇒ NoThunks (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

NoThunks (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

NoThunks (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

GetTip (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTipLedgerState (ShelleyBlock proto era) → Point (LedgerState (ShelleyBlock proto era)) Source #

GetTip (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTipTicked (LedgerState (ShelleyBlock proto era)) → Point (Ticked (LedgerState (ShelleyBlock proto era))) Source #

IsLedger (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

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

ApplyBlock (LedgerState ByronBlock) ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

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

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

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

data LedgerState ByronBlock Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type HeaderHash (LedgerState blk ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

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

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type Rep (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type Rep (LedgerState ByronBlock) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.16.0.0-inplace" 'False) (C1 ('MetaCons "ByronLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "byronLedgerTipBlockNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (WithOrigin BlockNo)) :*: (S1 ('MetaSel ('Just "byronLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainValidationState) :*: S1 ('MetaSel ('Just "byronLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByronTransition))))
type Rep (LedgerState (ShelleyBlock proto era)) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (LedgerState (ShelleyBlock proto era)) = D1 ('MetaData "LedgerState" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.16.0.0-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))))
type Rep (Ticked (LedgerState (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs))))
type Rep (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type Rep (Ticked (LedgerState ByronBlock)) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.16.0.0-inplace" 'False) (C1 ('MetaCons "TickedByronLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedByronLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainValidationState) :*: S1 ('MetaSel ('Just "untickedByronLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByronTransition)))
type Rep (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.16.0.0-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)))))
type AuxLedgerEvent (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type AuxLedgerEvent (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerCfg (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerCfg (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerErr (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerErr (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

newtype LedgerState (HardForkBlock xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

data Ticked (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState ByronBlock) Source #

The ticked Byron ledger state

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

data Ticked (LedgerState (ShelleyBlock proto era)) Source #

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data LedgerState (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

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

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

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

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

Minimal complete definition

applyShelleyBasedTx, getConwayEraGovDict

Instances

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

Defined in Ouroboros.Consensus.Shelley.Eras

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

Defined in Ouroboros.Consensus.Shelley.Eras

PraosCrypto c ⇒ ShelleyBasedEra (BabbageEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

PraosCrypto c ⇒ ShelleyBasedEra (ConwayEra c) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Eras

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

Defined in Ouroboros.Consensus.Shelley.Eras

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

Defined in Ouroboros.Consensus.Shelley.Eras

newtype ShelleyLedgerError era Source #

Constructors

BBodyError (BlockTransitionError era) 

Instances

Instances details
Generic (ShelleyLedgerError era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (ShelleyLedgerError era) ∷ TypeType #

ShelleyBasedEra era ⇒ Show (ShelleyLedgerError era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyBasedEra era ⇒ Eq (ShelleyLedgerError era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

ShelleyBasedEra era ⇒ NoThunks (ShelleyLedgerError era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (ShelleyLedgerError era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (ShelleyLedgerError era) = D1 ('MetaData "ShelleyLedgerError" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.16.0.0-inplace" 'True) (C1 ('MetaCons "BBodyError" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BlockTransitionError era))))

data ShelleyTip proto era Source #

Instances

Instances details
(ShelleyBasedEra era, ShelleyBasedEra (PreviousEra era), Era (PreviousEra era), EraCrypto (PreviousEra era) ~ EraCrypto era) ⇒ TranslateEra era (ShelleyTip proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (ShelleyTip proto) Source #

Methods

translateEraTranslationContext era → ShelleyTip proto (PreviousEra era) → Except (TranslationError era (ShelleyTip proto)) (ShelleyTip proto era) Source #

Generic (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (ShelleyTip proto era) ∷ TypeType #

Methods

fromShelleyTip proto era → Rep (ShelleyTip proto era) x #

toRep (ShelleyTip proto era) x → ShelleyTip proto era #

Show (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

showsPrecIntShelleyTip proto era → ShowS #

showShelleyTip proto era → String #

showList ∷ [ShelleyTip proto era] → ShowS #

Eq (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

(==)ShelleyTip proto era → ShelleyTip proto era → Bool #

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

NoThunks (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunksContextShelleyTip proto era → IO (Maybe ThunkInfo) Source #

wNoThunksContextShelleyTip proto era → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (ShelleyTip proto era) → String Source #

type TranslationError era (ShelleyTip proto) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (ShelleyTip proto) = Void
type Rep (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (ShelleyTip proto era) = D1 ('MetaData "ShelleyTip" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.16.0.0-inplace" 'False) (C1 ('MetaCons "ShelleyTip" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyTipSlotNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SlotNo) :*: (S1 ('MetaSel ('Just "shelleyTipBlockNo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlockNo) :*: S1 ('MetaSel ('Just "shelleyTipHash") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderHash (ShelleyBlock proto era))))))

newtype ShelleyTransition Source #

Information required to determine the hard fork point from Shelley to the next ledger

Constructors

ShelleyTransitionInfo 

Fields

  • shelleyAfterVotingWord32

    The number of blocks in this epoch past the voting deadline

    We record this to make sure that we can tell the HFC about hard forks if and only if we are certain:

    1. Blocks that came in within an epoch after the 4k/f voting deadline are not relevant (10kf - 2 * 3kf).
    2. Since there are slots between blocks, we are probably only sure that there will be no more relevant block when we have seen the first block after the deadline.
    3. If we count how many blocks we have seen post deadline, and we have reached k of them, we know that that last pre-deadline block won't be rolled back anymore.
    4. At this point we can look at the ledger state and see if there is a new protocol version update scheduled on the next epoch boundary, and notify the HFC that we need to transition into a new era at that point.

Instances

Instances details
Generic ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep ShelleyTransitionTypeType #

Show ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Eq ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

NoThunks ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep ShelleyTransition = D1 ('MetaData "ShelleyTransition" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.16.0.0-inplace" 'True) (C1 ('MetaCons "ShelleyTransitionInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyAfterVoting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

data family Ticked st Source #

" Ticked " piece of state, either LedgerState or ChainDepState

Ticking refers to the passage of time (the ticking of the clock). When a piece of state is marked as ticked, it means that time-related changes have been applied to the state. There are exactly two methods in the interface that do that: tickChainDepState and applyChainTickLedgerResult.

Also note that a successful forecast forecastFor (ledgerViewForecastAt cfg st) slot must equal protocolLedgerView cfg (applyChainTick cfg slot st). Thus a LedgerView can only be projected from a Ticked state, but cannot itself be ticked.

Some examples of time related changes:

  • Scheduled delegations might have been applied in Byron
  • New leader schedule computed for Shelley
  • Transition from Byron to Shelley activated in the hard fork combinator.
  • Nonces switched out at the start of a new epoch.

Instances

Instances details
Generic (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState ByronBlock)) ∷ TypeType #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) ∷ TypeType #

Methods

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

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

Show (Ticked ()) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS #

showTicked () → String #

showList ∷ [Ticked ()] → ShowS #

NoThunks (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

GetTip (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTipTicked (LedgerState (ShelleyBlock proto era)) → Point (Ticked (LedgerState (ShelleyBlock proto era))) Source #

IsLedger (LedgerState blk) ⇒ GetTip (Ticked (ExtLedgerState blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Show (Ticked (f a)) ⇒ Show ((Ticked :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecInt → (Ticked :.: f) a → ShowS #

show ∷ (Ticked :.: f) a → String #

showList ∷ [(Ticked :.: f) a] → ShowS #

NoThunks (Ticked (f a)) ⇒ NoThunks ((Ticked :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ Type) 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ Type) = HeaderHash l
type Rep (Ticked (LedgerState (HardForkBlock xs))) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type Rep (Ticked (LedgerState (HardForkBlock xs))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.HardFork.Combinator.Ledger" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "TickedHardForkLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedHardForkLedgerStateTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TransitionInfo) :*: S1 ('MetaSel ('Just "tickedHardForkLedgerStatePerEra") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HardForkState (Ticked :.: LedgerState) xs))))
type Rep (Ticked (LedgerState ByronBlock)) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type Rep (Ticked (LedgerState ByronBlock)) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Byron.Ledger.Ledger" "ouroboros-consensus-cardano-0.16.0.0-inplace" 'False) (C1 ('MetaCons "TickedByronLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "tickedByronLedgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ChainValidationState) :*: S1 ('MetaSel ('Just "untickedByronLedgerTransition") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 ByronTransition)))
type Rep (Ticked (LedgerState (ShelleyBlock proto era))) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) = D1 ('MetaData "Ticked" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.16.0.0-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)))))
data Ticked (HardForkChainDepState xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HeaderState blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState ByronBlock) Source #

The ticked Byron ledger state

Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

data Ticked (LedgerState (ShelleyBlock proto era)) Source #

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data Ticked (ExtLedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

data Ticked (PBftState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (WrapChainDepState blk) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

data Ticked (PraosState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

data Ticked (TPraosState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

castShelleyTipHeaderHash (ShelleyBlock proto era) ~ HeaderHash (ShelleyBlock proto' era') ⇒ ShelleyTip proto era → ShelleyTip proto' era' Source #

Ledger config

data ShelleyLedgerConfig era Source #

Constructors

ShelleyLedgerConfig 

Fields

Instances

Instances details
Generic (ShelleyLedgerConfig era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (ShelleyLedgerConfig era) ∷ TypeType #

(NoThunks (TranslationContext era), Era era) ⇒ NoThunks (ShelleyLedgerConfig era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (ShelleyLedgerConfig era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type Rep (ShelleyLedgerConfig era) = D1 ('MetaData "ShelleyLedgerConfig" "Ouroboros.Consensus.Shelley.Ledger.Ledger" "ouroboros-consensus-cardano-0.16.0.0-inplace" 'False) (C1 ('MetaCons "ShelleyLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyLedgerCompactGenesis") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CompactGenesis (EraCrypto era))) :*: (S1 ('MetaSel ('Just "shelleyLedgerGlobals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Globals) :*: S1 ('MetaSel ('Just "shelleyLedgerTranslationContext") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (TranslationContext era)))))

shelleyEraParamsNeverHardForksShelleyGenesis c → EraParams Source #

Separate variant of shelleyEraParams to be used for a Shelley-only chain.

Auxiliary

data ShelleyLedgerEvent era Source #

All events emitted by the Shelley ledger API

Constructors

ShelleyLedgerEventBBODY (Event (EraRule "BBODY" era))

An event emitted when (re)applying a block

ShelleyLedgerEventTICK (Event (EraRule "TICK" era))

An event emitted during the chain tick

getPParamsEraGov era ⇒ NewEpochState era → PParams era Source #

Serialisation

decodeShelleyLedgerState ∷ ∀ era proto s. ShelleyCompatible proto era ⇒ Decoder s (LedgerState (ShelleyBlock proto era)) Source #

Orphan instances

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

Associated Types

type Rep (LedgerState (ShelleyBlock proto era)) ∷ TypeType #

Methods

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

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

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

Associated Types

type Rep (Ticked (LedgerState (ShelleyBlock proto era))) ∷ TypeType #

Methods

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

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

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

Methods

showsPrecIntLedgerState (ShelleyBlock proto era) → ShowS #

showLedgerState (ShelleyBlock proto era) → String #

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

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

Methods

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

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

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

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

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

Methods

getTipLedgerState (ShelleyBlock proto era) → Point (LedgerState (ShelleyBlock proto era)) Source #

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

Methods

getTipTicked (LedgerState (ShelleyBlock proto era)) → Point (Ticked (LedgerState (ShelleyBlock proto era))) Source #

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

Associated Types

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

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

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

HasHardForkHistory (ShelleyBlock proto era) Source # 
Instance details

Associated Types

type HardForkIndices (ShelleyBlock proto era) ∷ [Type] Source #

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

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

Associated Types

type OtherHeaderEnvelopeError (ShelleyBlock proto era) Source #

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

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