ouroboros-consensus-0.25.0.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

Synopsis

Hard fork

data HardForkLedgerView_ (f ∷ TypeType) (xs ∷ [Type]) Source #

Constructors

HardForkLedgerView 

Fields

Type family instances

data family Ticked (st ∷ k) ∷ k 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
Show (Ticked ()) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS #

showTicked () → String #

showList ∷ [Ticked ()] → ShowS #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (HardForkBlock xs)) mk → Point (Ticked (LedgerState (HardForkBlock xs))) Source #

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

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (LedgerState (DualBlock m a)) mk → Point (Ticked (LedgerState (DualBlock m a))) Source #

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

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

getTip ∷ ∀ (mk ∷ MapKind). Ticked (ExtLedgerState blk) mk → Point (Ticked (ExtLedgerState blk)) Source #

(CanHardFork xs, HasCanonicalTxIn xs, HasHardForkTxOut xs) ⇒ HasLedgerTables (Ticked (LedgerState (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

(Bridge m a, NoThunks (TxOut (LedgerState m)), NoThunks (TxIn (LedgerState m)), Show (TxOut (LedgerState m)), Show (TxIn (LedgerState m)), Eq (TxOut (LedgerState m)), Ord (TxIn (LedgerState m)), MemPack (TxOut (LedgerState m)), MemPack (TxIn (LedgerState m))) ⇒ HasLedgerTables (Ticked (LedgerState (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

(HasLedgerTables (Ticked (LedgerState blk)), NoThunks (TxOut (LedgerState blk)), NoThunks (TxIn (LedgerState blk)), Show (TxOut (LedgerState blk)), Show (TxIn (LedgerState blk)), Eq (TxOut (LedgerState blk)), Ord (TxIn (LedgerState blk)), MemPack (TxIn (LedgerState blk)), MemPack (TxOut (LedgerState blk))) ⇒ HasLedgerTables (Ticked (ExtLedgerState blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

projectLedgerTables ∷ ∀ (mk ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (ExtLedgerState blk) mk → LedgerTables (Ticked (ExtLedgerState blk)) mk Source #

withLedgerTables ∷ ∀ (mk ∷ MapKind) (any ∷ MapKind). (CanMapMK mk, CanMapKeysMK mk, ZeroableMK mk) ⇒ Ticked (ExtLedgerState blk) any → LedgerTables (Ticked (ExtLedgerState blk)) mk → Ticked (ExtLedgerState blk) mk Source #

LedgerTablesAreTrivial (Ticked (LedgerState blk)) ⇒ LedgerTablesAreTrivial (Ticked (ExtLedgerState blk)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

convertMapKind ∷ ∀ (mk ∷ MapKind) (mk' ∷ MapKind). Ticked (ExtLedgerState blk) mk → Ticked (ExtLedgerState blk) mk' Source #

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

Defined in Ouroboros.Consensus.Ledger.Dual

Show (Ticked (f a)) ⇒ Show (((TickedTypeType) :.: f) a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

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

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

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

NoThunks (Ticked (f a)) ⇒ NoThunks (((TickedTypeType) :.: f) a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

noThunksContext → ((TickedTypeType) :.: f) a → IO (Maybe ThunkInfo) Source #

wNoThunksContext → ((TickedTypeType) :.: f) a → IO (Maybe ThunkInfo) Source #

showTypeOfProxy (((TickedTypeType) :.: f) a) → String Source #

data Ticked () Source # 
Instance details

Defined in Ouroboros.Consensus.Ticked

data Ticked (HardForkChainDepState xs ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol

data Ticked (HeaderState blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (PBftState c ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

newtype Ticked (WrapChainDepState blk ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

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

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l ∷ k) = HeaderHash l
type TxIn (Ticked l) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxIn (Ticked l) = TxIn l
type TxOut (Ticked l) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Tables.Basics

type TxOut (Ticked l) = TxOut l
data Ticked (LedgerState (HardForkBlock xs) ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

data Ticked (LedgerState (DualBlock m a) ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data Ticked (ExtLedgerState blk ∷ MapKindType) (mk ∷ MapKind) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended