ouroboros-consensus-cardano-0.12.1.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 #

Instances

Instances details
Inject LedgerState 
Instance details

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

Methods

inject :: forall x (xs :: [Type]). CanHardFork xs => Exactly xs Bound -> Index xs x -> LedgerState x -> LedgerState (HardForkBlock xs)

DecodeDisk ByronBlock (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Node.Serialisation

Methods

decodeDisk :: CodecConfig ByronBlock -> forall s. Decoder s (LedgerState ByronBlock)

EncodeDisk ByronBlock (LedgerState ByronBlock) 
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) 
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)

Generic (LedgerState ByronBlock) Source # 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type Rep (LedgerState ByronBlock) :: Type -> Type Source #

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (LedgerState (ShelleyBlock proto era)) :: Type -> Type Source #

Methods

from :: LedgerState (ShelleyBlock proto era) -> Rep (LedgerState (ShelleyBlock proto era)) x Source #

to :: Rep (LedgerState (ShelleyBlock proto era)) x -> LedgerState (ShelleyBlock proto era) Source #

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

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState ByronBlock)) :: Type -> Type 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))) :: Type -> Type Source #

Methods

from :: Ticked (LedgerState (ShelleyBlock proto era)) -> Rep (Ticked (LedgerState (ShelleyBlock proto era))) x Source #

to :: Rep (Ticked (LedgerState (ShelleyBlock proto era))) x -> Ticked (LedgerState (ShelleyBlock proto era)) Source #

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

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

(/=) :: LedgerState (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> Bool 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)

showTypeOf :: Proxy (LedgerState (HardForkBlock xs)) -> String

NoThunks (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

noThunks :: Context -> LedgerState ByronBlock -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> LedgerState ByronBlock -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (LedgerState ByronBlock) -> String

ShelleyBasedEra era => NoThunks (LedgerState (ShelleyBlock proto era)) 
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)

showTypeOf :: Proxy (LedgerState (ShelleyBlock proto era)) -> String

NoThunks (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

noThunks :: Context -> Ticked (LedgerState ByronBlock) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Ticked (LedgerState ByronBlock) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Ticked (LedgerState ByronBlock)) -> String

ShelleyBasedEra era => NoThunks (Ticked (LedgerState (ShelleyBlock proto era))) 
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)

showTypeOf :: Proxy (Ticked (LedgerState (ShelleyBlock proto era))) -> String

GetTip (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

GetTip (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTip :: LedgerState (ShelleyBlock proto era) -> Point (LedgerState (ShelleyBlock proto era))

GetTip (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTip :: Ticked (LedgerState (ShelleyBlock proto era)) -> Point (Ticked (LedgerState (ShelleyBlock proto era)))

IsLedger (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type LedgerErr (LedgerState ByronBlock)

type AuxLedgerEvent (LedgerState ByronBlock)

ShelleyBasedEra era => IsLedger (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type LedgerErr (LedgerState (ShelleyBlock proto era))

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era))

Methods

applyChainTickLedgerResult :: LedgerCfg (LedgerState (ShelleyBlock proto era)) -> SlotNo -> LedgerState (ShelleyBlock proto era) -> LedgerResult (LedgerState (ShelleyBlock proto era)) (Ticked (LedgerState (ShelleyBlock proto era)))

ApplyBlock (LedgerState ByronBlock) ByronBlock 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

ShelleyCompatible proto era => ApplyBlock (LedgerState (ShelleyBlock proto era)) (ShelleyBlock proto era) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

applyBlockLedgerResult :: LedgerCfg (LedgerState (ShelleyBlock proto era)) -> ShelleyBlock proto era -> Ticked (LedgerState (ShelleyBlock proto era)) -> Except (LedgerErr (LedgerState (ShelleyBlock proto era))) (LedgerResult (LedgerState (ShelleyBlock proto era)) (LedgerState (ShelleyBlock proto era)))

reapplyBlockLedgerResult :: LedgerCfg (LedgerState (ShelleyBlock proto era)) -> ShelleyBlock proto era -> Ticked (LedgerState (ShelleyBlock proto era)) -> LedgerResult (LedgerState (ShelleyBlock proto era)) (LedgerState (ShelleyBlock proto era))

ShelleyCompatible proto era => DecodeDisk (ShelleyBlock proto era) (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

decodeDisk :: CodecConfig (ShelleyBlock proto era) -> forall s. Decoder s (LedgerState (ShelleyBlock proto era))

ShelleyCompatible proto era => EncodeDisk (ShelleyBlock proto era) (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Node.Serialisation

Methods

encodeDisk :: CodecConfig (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> Encoding

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

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type TranslationError era (LedgerState :.: ShelleyBlock proto) = Void
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.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" '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.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" '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.14.0.0-121Znn1OCbJFCod8haNyF" '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.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" '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.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" '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 (HardForkBlock xs)) = OneEraLedgerEvent xs
type AuxLedgerEvent (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type AuxLedgerEvent (LedgerState ByronBlock) = VoidLedgerEvent (LedgerState ByronBlock)
type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerEvent era
type LedgerCfg (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Basics

type LedgerCfg (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type LedgerCfg (LedgerState ByronBlock) = Config
type LedgerCfg (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerCfg (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerConfig era
type LedgerErr (LedgerState (HardForkBlock xs)) 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Ledger

type LedgerErr (LedgerState (HardForkBlock xs)) = HardForkLedgerError xs
type LedgerErr (LedgerState ByronBlock) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

type LedgerErr (LedgerState ByronBlock) = ChainValidationError
type LedgerErr (LedgerState (ShelleyBlock proto era)) 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

type LedgerErr (LedgerState (ShelleyBlock proto era)) = ShelleyLedgerError era
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/input-output-hk/ouroboros-network/issues/2890

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 #

getProposedProtocolVersion :: PParamsUpdate (AllegraEra c) -> Maybe ProtVer 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 #

getProposedProtocolVersion :: PParamsUpdate (AlonzoEra c) -> Maybe ProtVer 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 #

getProposedProtocolVersion :: PParamsUpdate (BabbageEra c) -> Maybe ProtVer 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 #

getProposedProtocolVersion :: PParamsUpdate (ConwayEra c) -> Maybe ProtVer 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 #

getProposedProtocolVersion :: PParamsUpdate (MaryEra c) -> Maybe ProtVer 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 #

getProposedProtocolVersion :: PParamsUpdate (ShelleyEra c) -> Maybe ProtVer Source #

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

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

Methods

noThunks :: Context -> ShelleyLedgerError era -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ShelleyLedgerError era -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (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-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'True) (C1 ('MetaCons "BBodyError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (BlockTransitionError era))))

data ShelleyTip proto era Source #

Constructors

ShelleyTip 

Fields

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)

Generic (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep (ShelleyTip proto era) :: Type -> Type Source #

Methods

from :: ShelleyTip proto era -> Rep (ShelleyTip proto era) x Source #

to :: Rep (ShelleyTip proto era) x -> ShelleyTip proto era Source #

Show (ShelleyTip proto era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

showsPrec :: Int -> ShelleyTip proto era -> ShowS Source #

show :: ShelleyTip proto era -> String Source #

showList :: [ShelleyTip proto era] -> ShowS Source #

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 #

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)

showTypeOf :: Proxy (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-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" '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

  • shelleyAfterVoting :: Word32

    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
Generic ShelleyTransition Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Associated Types

type Rep ShelleyTransition :: Type -> Type Source #

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

Methods

noThunks :: Context -> ShelleyTransition -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> ShelleyTransition -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy ShelleyTransition -> String

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.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'True) (C1 ('MetaCons "ShelleyTransitionInfo" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyAfterVoting") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Word32)))

data family Ticked st #

Instances

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

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Associated Types

type Rep (Ticked (LedgerState ByronBlock)) :: Type -> Type 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))) :: Type -> Type Source #

Methods

from :: Ticked (LedgerState (ShelleyBlock proto era)) -> Rep (Ticked (LedgerState (ShelleyBlock proto era))) x Source #

to :: Rep (Ticked (LedgerState (ShelleyBlock proto era))) x -> Ticked (LedgerState (ShelleyBlock proto era)) Source #

Show (Ticked ()) 
Instance details

Defined in Ouroboros.Consensus.Ticked

NoThunks (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

Methods

noThunks :: Context -> Ticked (LedgerState ByronBlock) -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> Ticked (LedgerState ByronBlock) -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy (Ticked (LedgerState ByronBlock)) -> String

ShelleyBasedEra era => NoThunks (Ticked (LedgerState (ShelleyBlock proto era))) 
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)

showTypeOf :: Proxy (Ticked (LedgerState (ShelleyBlock proto era))) -> String

GetTip (Ticked (LedgerState ByronBlock)) 
Instance details

Defined in Ouroboros.Consensus.Byron.Ledger.Ledger

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

Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger

Methods

getTip :: Ticked (LedgerState (ShelleyBlock proto era)) -> Point (Ticked (LedgerState (ShelleyBlock proto era)))

IsLedger (LedgerState blk) => GetTip (Ticked (ExtLedgerState blk)) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Extended

Methods

getTip :: Ticked (ExtLedgerState blk) -> Point (Ticked (ExtLedgerState blk))

Show (Ticked (f a)) => Show ((Ticked :.: f) a) 
Instance details

Defined in Ouroboros.Consensus.Ticked

Methods

showsPrec :: Int -> (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)

showTypeOf :: Proxy ((Ticked :.: f) a) -> String

data Ticked () 
Instance details

Defined in Ouroboros.Consensus.Ticked

type HeaderHash (Ticked l :: Type) 
Instance details

Defined in Ouroboros.Consensus.Ledger.Basics

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.14.0.0-121Znn1OCbJFCod8haNyF" '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.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" '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.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" '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 (HardForkChainDepState xs) = TickedHardForkChainDepState {}
data Ticked (HeaderState blk) 
Instance details

Defined in Ouroboros.Consensus.HeaderValidation

data Ticked (HeaderState blk) = TickedHeaderState {}
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 (ExtLedgerState blk) = TickedExtLedgerState {}
data Ticked (PBftState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.PBFT

data Ticked (PBftState c) = TickedPBftState {}
newtype Ticked (WrapChainDepState blk) 
Instance details

Defined in Ouroboros.Consensus.TypeFamilyWrappers

newtype Ticked (WrapChainDepState blk) = WrapTickedChainDepState {}
data Ticked (PraosState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.Praos

data Ticked (PraosState c) = TickedPraosState {}
data Ticked (TPraosState c) 
Instance details

Defined in Ouroboros.Consensus.Protocol.TPraos

data Ticked (TPraosState c) = TickedChainDepState {}

castShelleyTip :: HeaderHash (ShelleyBlock proto era) ~ HeaderHash (ShelleyBlock proto' era') => ShelleyTip proto era -> ShelleyTip proto' era' Source #

shelleyTipToPoint :: WithOrigin (ShelleyTip proto era) -> Point (ShelleyBlock 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) :: Type -> Type 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)

showTypeOf :: Proxy (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-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" '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)))))

mkShelleyLedgerConfig :: ShelleyGenesis (EraCrypto era) -> TranslationContext era -> EpochInfo (Except PastHorizonException) -> MaxMajorProtVer -> ShelleyLedgerConfig era Source #

shelleyEraParamsNeverHardForks :: ShelleyGenesis 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 :: EraGov era => NewEpochState era -> PParams era Source #

Serialisation

decodeShelleyAnnTip :: ShelleyCompatible proto era => Decoder s (AnnTip (ShelleyBlock proto era)) Source #

decodeShelleyLedgerState :: forall era proto s. ShelleyCompatible proto era => Decoder s (LedgerState (ShelleyBlock proto era)) Source #

encodeShelleyAnnTip :: ShelleyCompatible proto era => AnnTip (ShelleyBlock proto era) -> Encoding Source #

encodeShelleyHeaderState :: ShelleyCompatible proto era => HeaderState (ShelleyBlock proto era) -> Encoding Source #

Orphan instances

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

Associated Types

type Rep (LedgerState (ShelleyBlock proto era)) :: Type -> Type Source #

Methods

from :: LedgerState (ShelleyBlock proto era) -> Rep (LedgerState (ShelleyBlock proto era)) x Source #

to :: Rep (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))) :: Type -> Type Source #

Methods

from :: Ticked (LedgerState (ShelleyBlock proto era)) -> Rep (Ticked (LedgerState (ShelleyBlock proto era))) x Source #

to :: Rep (Ticked (LedgerState (ShelleyBlock proto era))) x -> Ticked (LedgerState (ShelleyBlock proto era)) Source #

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

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 => 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)

showTypeOf :: Proxy (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)

showTypeOf :: Proxy (Ticked (LedgerState (ShelleyBlock proto era))) -> String

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

Methods

getTip :: LedgerState (ShelleyBlock proto era) -> Point (LedgerState (ShelleyBlock proto era))

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

Methods

getTip :: Ticked (LedgerState (ShelleyBlock proto era)) -> Point (Ticked (LedgerState (ShelleyBlock proto era)))

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

Associated Types

type LedgerErr (LedgerState (ShelleyBlock proto era))

type AuxLedgerEvent (LedgerState (ShelleyBlock proto era))

Methods

applyChainTickLedgerResult :: LedgerCfg (LedgerState (ShelleyBlock proto era)) -> SlotNo -> LedgerState (ShelleyBlock proto era) -> LedgerResult (LedgerState (ShelleyBlock proto era)) (Ticked (LedgerState (ShelleyBlock proto era)))

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

Methods

applyBlockLedgerResult :: LedgerCfg (LedgerState (ShelleyBlock proto era)) -> ShelleyBlock proto era -> Ticked (LedgerState (ShelleyBlock proto era)) -> Except (LedgerErr (LedgerState (ShelleyBlock proto era))) (LedgerResult (LedgerState (ShelleyBlock proto era)) (LedgerState (ShelleyBlock proto era)))

reapplyBlockLedgerResult :: LedgerCfg (LedgerState (ShelleyBlock proto era)) -> ShelleyBlock proto era -> Ticked (LedgerState (ShelleyBlock proto era)) -> LedgerResult (LedgerState (ShelleyBlock proto era)) (LedgerState (ShelleyBlock proto era))

HasHardForkHistory (ShelleyBlock proto era) Source # 
Instance details

Associated Types

type HardForkIndices (ShelleyBlock proto era) :: [Type]

Methods

hardForkSummary :: LedgerConfig (ShelleyBlock proto era) -> LedgerState (ShelleyBlock proto era) -> Summary (HardForkIndices (ShelleyBlock proto era))

ShelleyCompatible proto era => BasicEnvelopeValidation (ShelleyBlock proto era) Source # 
Instance details

Methods

expectedFirstBlockNo :: proxy (ShelleyBlock proto era) -> BlockNo

expectedNextBlockNo :: proxy (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> BlockNo -> BlockNo

minimumPossibleSlotNo :: Proxy (ShelleyBlock proto era) -> SlotNo

minimumNextSlotNo :: proxy (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> TipInfo (ShelleyBlock proto era) -> SlotNo -> SlotNo

ShelleyCompatible proto era => ValidateEnvelope (ShelleyBlock proto era) Source # 
Instance details

Associated Types

type OtherHeaderEnvelopeError (ShelleyBlock proto era)

Methods

additionalEnvelopeChecks :: TopLevelConfig (ShelleyBlock proto era) -> LedgerView (BlockProtocol (ShelleyBlock proto era)) -> Header (ShelleyBlock proto era) -> Except (OtherHeaderEnvelopeError (ShelleyBlock proto era)) ()

ShelleyCompatible proto era => UpdateLedger (ShelleyBlock proto era) Source # 
Instance details

ShelleyCompatible proto era => CommonProtocolParams (ShelleyBlock proto era) Source # 
Instance details