ouroboros-consensus-shelley-0.4.0.0: Shelley ledger integration in the Ouroboros consensus layer
Safe HaskellNone
LanguageHaskell2010

Ouroboros.Consensus.Shelley.Ledger.Ledger

Synopsis

Documentation

data family LedgerState blk Source #

Ledger state associated with a block

Instances

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

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (LedgerState :.: ShelleyBlock proto)

Methods

translateEra ∷ TranslationContext era → (LedgerState :.: ShelleyBlock proto) (PreviousEra era) → Except (TranslationError era (LedgerState :.: ShelleyBlock proto)) ((LedgerState :.: ShelleyBlock proto) era)

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

showsPrecIntLedgerState (ShelleyBlock proto era) → ShowS Source #

showLedgerState (ShelleyBlock proto era) → String Source #

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

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

Methods

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

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

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

Methods

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

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

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

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 #

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

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

Methods

noThunks ∷ Context → LedgerState (HardForkBlock xs) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → LedgerState (HardForkBlock xs) → IO (Maybe ThunkInfo) #

showTypeOfProxy (LedgerState (HardForkBlock xs)) → String #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks ∷ Context → LedgerState (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → LedgerState (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (LedgerState (ShelleyBlock proto era)) → String #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks ∷ Context → Ticked (LedgerState (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (ShelleyBlock proto era))) → String #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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 #

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 #

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

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (LedgerState :.: ShelleyBlock proto) = Void
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-shelley-0.4.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.3.1.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 (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-shelley-0.4.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 LedgerCfg (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type AuxLedgerEvent (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

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

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type HeaderHash (LedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

data LedgerState (ShelleyBlock proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

class (EraSegWits era, EraGovernance era, ApplyTx era, ApplyBlock era, CanStartFromGenesis 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 "DELEGS" era)), EncCBOR (PredicateFailure (EraRule "DELEGS" era)), DecCBOR (PredicateFailure (EraRule "UTXOW" era)), EncCBOR (PredicateFailure (EraRule "UTXOW" era)), DSignable (EraCrypto era) (Hash (EraCrypto era) EraIndependentTxBody), NoThunks (PredicateFailure (EraRule "BBODY" era)), NoThunks (TranslationContext era)) ⇒ ShelleyBasedEra era Source #

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

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

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

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

Minimal complete definition

shelleyBasedEraName, applyShelleyBasedTx

Instances

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

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName ∷ proxy (AllegraEra c) → Text Source #

applyShelleyBasedTx ∷ Globals → LedgerEnv (AllegraEra c) → LedgerState (AllegraEra c) → WhetherToIntervene → Tx (AllegraEra c) → Except (ApplyTxError (AllegraEra c)) (LedgerState (AllegraEra c), Validated (Tx (AllegraEra c))) Source #

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

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName ∷ proxy (ShelleyEra c) → Text Source #

applyShelleyBasedTx ∷ Globals → LedgerEnv (ShelleyEra c) → LedgerState (ShelleyEra c) → WhetherToIntervene → Tx (ShelleyEra c) → Except (ApplyTxError (ShelleyEra c)) (LedgerState (ShelleyEra c), Validated (Tx (ShelleyEra c))) Source #

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

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName ∷ proxy (AlonzoEra c) → Text Source #

applyShelleyBasedTx ∷ Globals → LedgerEnv (AlonzoEra c) → LedgerState (AlonzoEra c) → WhetherToIntervene → Tx (AlonzoEra c) → Except (ApplyTxError (AlonzoEra c)) (LedgerState (AlonzoEra c), Validated (Tx (AlonzoEra c))) Source #

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

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName ∷ proxy (MaryEra c) → Text Source #

applyShelleyBasedTx ∷ Globals → LedgerEnv (MaryEra c) → LedgerState (MaryEra c) → WhetherToIntervene → Tx (MaryEra c) → Except (ApplyTxError (MaryEra c)) (LedgerState (MaryEra c), Validated (Tx (MaryEra c))) Source #

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

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName ∷ proxy (BabbageEra c) → Text Source #

applyShelleyBasedTx ∷ Globals → LedgerEnv (BabbageEra c) → LedgerState (BabbageEra c) → WhetherToIntervene → Tx (BabbageEra c) → Except (ApplyTxError (BabbageEra c)) (LedgerState (BabbageEra c), Validated (Tx (BabbageEra c))) Source #

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

Defined in Ouroboros.Consensus.Shelley.Eras

Methods

shelleyBasedEraName ∷ proxy (ConwayEra c) → Text Source #

applyShelleyBasedTx ∷ Globals → LedgerEnv (ConwayEra c) → LedgerState (ConwayEra c) → WhetherToIntervene → Tx (ConwayEra c) → Except (ApplyTxError (ConwayEra c)) (LedgerState (ConwayEra c), Validated (Tx (ConwayEra c))) Source #

newtype ShelleyLedgerError era Source #

Constructors

BBodyError (BlockTransitionError era) 

Instances

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Generic (ShelleyLedgerError era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (ShelleyLedgerError era) ∷ TypeType Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks ∷ Context → ShelleyLedgerError era → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ShelleyLedgerError era → IO (Maybe ThunkInfo) #

showTypeOfProxy (ShelleyLedgerError era) → String #

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-shelley-0.4.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) 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type TranslationError era (ShelleyTip proto)

Methods

translateEra ∷ TranslationContext era → ShelleyTip proto (PreviousEra era) → Except (TranslationError era (ShelleyTip proto)) (ShelleyTip proto era)

Eq (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

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

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

Show (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

showsPrecIntShelleyTip proto era → ShowS Source #

showShelleyTip proto era → String Source #

showList ∷ [ShelleyTip proto era] → ShowS Source #

Generic (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (ShelleyTip proto era) ∷ TypeType Source #

Methods

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

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

NoThunks (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks ∷ Context → ShelleyTip proto era → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ShelleyTip proto era → IO (Maybe ThunkInfo) #

showTypeOfProxy (ShelleyTip proto era) → String #

type TranslationError era (ShelleyTip proto) 
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-shelley-0.4.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 which proposals we accepted in the voting period, if any, and notify the HFC is one of them indicates a transition.

Instances

Instances details
Eq ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Show ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Generic ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep ShelleyTransitionTypeType Source #

NoThunks ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks ∷ Context → ShelleyTransitionIO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ShelleyTransitionIO (Maybe ThunkInfo) #

showTypeOfProxy ShelleyTransitionString #

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-shelley-0.4.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 (LedgerState, LedgerView, ChainIndepState)

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 (or forecast).

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 ()) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked () → ShowS Source #

showTicked () → String Source #

showList ∷ [Ticked ()] → ShowS Source #

(SListI xs, Show (Ticked a)) ⇒ Show (Ticked (HardForkLedgerView_ (K a ∷ TypeType) xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

Show (Ticked a) ⇒ Show (Ticked (K a x)) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrecIntTicked (K a x) → ShowS Source #

showTicked (K a x) → String Source #

showList ∷ [Ticked (K a x)] → ShowS Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

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

Methods

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

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

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

Defined in Ouroboros.Consensus.Ledger.Extended

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 #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks ∷ Context → Ticked (LedgerState (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (ShelleyBlock proto era))) → String #

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

Defined in Ouroboros.Consensus.Ticked

Methods

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

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

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

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

Defined in Ouroboros.Consensus.Ticked

Methods

noThunks ∷ Context → (Ticked :.: f) a → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → (Ticked :.: f) a → IO (Maybe ThunkInfo) #

showTypeOfProxy ((Ticked :.: f) a) → String #

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

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.3.1.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 (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-shelley-0.4.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 (ExtLedgerState blk) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

newtype Ticked (WrapChainDepState blk) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

newtype Ticked (WrapLedgerView blk) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

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

Ticking only affects the state itself

Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

data Ticked (PraosState c)

Ticked PraosState

Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

data Ticked (TPraosState c)

Ticked TPraosState

Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

newtype Ticked (LedgerView c)

Ledger view at a particular slot

Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

newtype Ticked (LedgerView c)

Ledger view at a particular slot

Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

newtype Ticked (LedgerView c) = TickedPraosLedgerView {}
type HeaderHash (Ticked l) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

data Ticked (HardForkLedgerView_ f xs) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Protocol.LedgerView

newtype Ticked (K a x) 
Instance details

Defined in Ouroboros.Consensus.Ticked

newtype Ticked (K a x) = TickedK {}

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

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

noThunks ∷ Context → ShelleyLedgerConfig era → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → ShelleyLedgerConfig era → IO (Maybe ThunkInfo) #

showTypeOfProxy (ShelleyLedgerConfig era) → String #

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-shelley-0.4.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

getPParams ∷ NewEpochState era → PParams era Source #

Serialisation

decodeShelleyAnnTipShelleyCompatible proto era ⇒ Decoder s (AnnTip (ShelleyBlock proto era)) Source #

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

encodeShelleyAnnTipShelleyCompatible proto era ⇒ AnnTip (ShelleyBlock proto era) → Encoding Source #

encodeShelleyHeaderStateShelleyCompatible proto era ⇒ HeaderState (ShelleyBlock proto era) → Encoding Source #

encodeShelleyLedgerStateShelleyCompatible proto era ⇒ LedgerState (ShelleyBlock proto era) → Encoding Source #

Orphan instances

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

Methods

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

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

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

Methods

showsPrecIntLedgerState (ShelleyBlock proto era) → ShowS Source #

showLedgerState (ShelleyBlock proto era) → String Source #

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

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

Associated Types

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

Methods

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

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

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

Associated Types

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

Methods

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

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

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 #

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

Methods

noThunks ∷ Context → LedgerState (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → LedgerState (ShelleyBlock proto era) → IO (Maybe ThunkInfo) #

showTypeOfProxy (LedgerState (ShelleyBlock proto era)) → String #

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

Methods

noThunks ∷ Context → Ticked (LedgerState (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

wNoThunks ∷ Context → Ticked (LedgerState (ShelleyBlock proto era)) → IO (Maybe ThunkInfo) #

showTypeOfProxy (Ticked (LedgerState (ShelleyBlock proto era))) → String #

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

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