ouroboros-consensus-0.18.0.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Consensus.Ledger.Extended

Synopsis

Extended ledger state

newtype ExtLedgerCfg blk Source #

" Ledger " configuration for the extended ledger

Since the extended ledger also does the consensus protocol validation, we also need the consensus config.

Constructors

ExtLedgerCfg 

Instances

Instances details
Generic (ExtLedgerCfg blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Associated Types

type Rep (ExtLedgerCfg blk) ∷ TypeType #

Methods

fromExtLedgerCfg blk → Rep (ExtLedgerCfg blk) x #

toRep (ExtLedgerCfg blk) x → ExtLedgerCfg blk #

(ConsensusProtocol (BlockProtocol blk), NoThunks (BlockConfig blk), NoThunks (CodecConfig blk), NoThunks (LedgerConfig blk), NoThunks (StorageConfig blk), NoThunks (HeaderHash blk)) ⇒ NoThunks (ExtLedgerCfg blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtLedgerCfg blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtLedgerCfg blk) = D1 ('MetaData "ExtLedgerCfg" "Ouroboros.Consensus.Ledger.Extended" "ouroboros-consensus-0.18.0.0-inplace" 'True) (C1 ('MetaCons "ExtLedgerCfg" 'PrefixI 'True) (S1 ('MetaSel ('Just "getExtLedgerCfg") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TopLevelConfig blk))))

data ExtLedgerState blk Source #

Extended ledger state

This is the combination of the header state and the ledger state proper.

Constructors

ExtLedgerState 

Fields

Instances

Instances details
Inject ExtLedgerState Source # 
Instance details

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

Methods

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

Isomorphic ExtLedgerState Source # 
Instance details

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

Generic (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Associated Types

type Rep (ExtLedgerState blk) ∷ TypeType #

Methods

fromExtLedgerState blk → Rep (ExtLedgerState blk) x #

toRep (ExtLedgerState blk) x → ExtLedgerState blk #

LedgerSupportsProtocol blk ⇒ Show (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

showsPrecIntExtLedgerState blk → ShowS #

showExtLedgerState blk → String #

showList ∷ [ExtLedgerState blk] → ShowS #

LedgerSupportsProtocol blk ⇒ Eq (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

(==)ExtLedgerState blk → ExtLedgerState blk → Bool #

(/=)ExtLedgerState blk → ExtLedgerState blk → Bool #

LedgerSupportsProtocol blk ⇒ NoThunks (ExtLedgerState blk) Source #

We override showTypeOf to show the type of the block

This makes debugging a bit easier, as the block gets used to resolve all kinds of type families.

Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

IsLedger (LedgerState blk) ⇒ GetTip (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

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

Defined in Ouroboros.Consensus.Ledger.Extended

LedgerSupportsProtocol blk ⇒ IsLedger (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Associated Types

type LedgerErr (ExtLedgerState blk) Source #

type AuxLedgerEvent (ExtLedgerState blk) Source #

LedgerSupportsProtocol blk ⇒ ApplyBlock (ExtLedgerState blk) blk Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type HeaderHash (ExtLedgerState blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtLedgerState blk) = D1 ('MetaData "ExtLedgerState" "Ouroboros.Consensus.Ledger.Extended" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "ExtLedgerState" 'PrefixI 'True) (S1 ('MetaSel ('Just "ledgerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerState blk)) :*: S1 ('MetaSel ('Just "headerState") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderState blk))))
type AuxLedgerEvent (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type LedgerCfg (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type LedgerErr (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

data Ticked (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

data ExtValidationError blk Source #

Instances

Instances details
Generic (ExtValidationError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Associated Types

type Rep (ExtValidationError blk) ∷ TypeType #

LedgerSupportsProtocol blk ⇒ Show (ExtValidationError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

LedgerSupportsProtocol blk ⇒ Eq (ExtValidationError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

LedgerSupportsProtocol blk ⇒ NoThunks (ExtValidationError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtValidationError blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

type Rep (ExtValidationError blk) = D1 ('MetaData "ExtValidationError" "Ouroboros.Consensus.Ledger.Extended" "ouroboros-consensus-0.18.0.0-inplace" 'False) (C1 ('MetaCons "ExtValidationErrorLedger" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerError blk))) :+: C1 ('MetaCons "ExtValidationErrorHeader" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (HeaderError blk))))

Serialisation

decodeExtLedgerState ∷ (∀ s. Decoder s (LedgerState blk)) → (∀ s. Decoder s (ChainDepState (BlockProtocol blk))) → (∀ s. Decoder s (AnnTip blk)) → ∀ s. Decoder s (ExtLedgerState blk) Source #

Casts

Type family instances

data family Ticked st ∷ Type 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 (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Associated Types

type Rep (Ticked (LedgerState (HardForkBlock xs))) ∷ TypeType #

Show (Ticked ()) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS #

showTicked () → String #

showList ∷ [Ticked ()] → ShowS #

CanHardFork xs ⇒ NoThunks (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

NoThunks (Ticked (LedgerState (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ GetTip (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Bridge m a ⇒ GetTip (Ticked (LedgerState (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

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

Defined in Ouroboros.Consensus.Ledger.Extended

Isomorphic (Ticked :.: LedgerState) Source # 
Instance details

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

Show (Ticked (f a)) ⇒ Show ((Ticked :.: f) a) Source # 
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) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

data Ticked () Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ Type) = HeaderHash l
type Rep (Ticked (LedgerState (HardForkBlock xs))) Source # 
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))))
data Ticked (HardForkChainDepState xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HeaderState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (LedgerState (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data Ticked (ExtLedgerState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

data Ticked (PBftState c) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (WrapChainDepState blk) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers