Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Ouroboros.Consensus.Shelley.Ledger.Ledger
Synopsis
- data family LedgerState blk
- 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
- newtype ShelleyLedgerError era = BBodyError (BlockTransitionError era)
- data ShelleyTip proto era = ShelleyTip {
- shelleyTipSlotNo :: !SlotNo
- shelleyTipBlockNo :: !BlockNo
- shelleyTipHash :: !(HeaderHash (ShelleyBlock proto era))
- newtype ShelleyTransition = ShelleyTransitionInfo {}
- data family Ticked st
- castShelleyTip :: HeaderHash (ShelleyBlock proto era) ~ HeaderHash (ShelleyBlock proto' era') => ShelleyTip proto era -> ShelleyTip proto' era'
- shelleyLedgerTipPoint :: LedgerState (ShelleyBlock proto era) -> Point (ShelleyBlock proto era)
- shelleyTipToPoint :: WithOrigin (ShelleyTip proto era) -> Point (ShelleyBlock proto era)
- data ShelleyLedgerConfig era = ShelleyLedgerConfig {
- shelleyLedgerCompactGenesis :: !(CompactGenesis (EraCrypto era))
- shelleyLedgerGlobals :: !Globals
- shelleyLedgerTranslationContext :: !(TranslationContext era)
- mkShelleyLedgerConfig :: ShelleyGenesis (EraCrypto era) -> TranslationContext era -> EpochInfo (Except PastHorizonException) -> MaxMajorProtVer -> ShelleyLedgerConfig era
- shelleyEraParams :: ShelleyGenesis c -> EraParams
- shelleyEraParamsNeverHardForks :: ShelleyGenesis c -> EraParams
- shelleyLedgerGenesis :: ShelleyLedgerConfig era -> ShelleyGenesis (EraCrypto era)
- data ShelleyLedgerEvent era
- = ShelleyLedgerEventBBODY (Event (EraRule "BBODY" era))
- | ShelleyLedgerEventTICK (Event (EraRule "TICK" era))
- data ShelleyReapplyException = forall era.Show (BlockTransitionError era) => ShelleyReapplyException (BlockTransitionError era)
- getPParams :: EraGov era => NewEpochState era -> PParams era
- decodeShelleyAnnTip :: ShelleyCompatible proto era => Decoder s (AnnTip (ShelleyBlock proto era))
- decodeShelleyLedgerState :: forall era proto s. ShelleyCompatible proto era => Decoder s (LedgerState (ShelleyBlock proto era))
- encodeShelleyAnnTip :: ShelleyCompatible proto era => AnnTip (ShelleyBlock proto era) -> Encoding
- encodeShelleyHeaderState :: ShelleyCompatible proto era => HeaderState (ShelleyBlock proto era) -> Encoding
- encodeShelleyLedgerState :: ShelleyCompatible proto era => LedgerState (ShelleyBlock proto era) -> Encoding
Documentation
data family LedgerState blk #
Instances
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
Minimal complete definition
shelleyBasedEraName, applyShelleyBasedTx, getProposedProtocolVersion
Instances
(PraosCrypto c, DSignable c (Hash c EraIndependentTxBody)) => ShelleyBasedEra (AllegraEra c) Source # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
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
data ShelleyTip proto era Source #
Constructors
ShelleyTip | |
Fields
|
Instances
(ShelleyBasedEra era, ShelleyBasedEra (PreviousEra era), Era (PreviousEra era), EraCrypto (PreviousEra era) ~ EraCrypto era) => TranslateEra era (ShelleyTip proto) | |
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 # | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger 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 # | |
Defined in Ouroboros.Consensus.Shelley.Ledger.Ledger | |
Eq (ShelleyTip proto era) Source # | |
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 # | |
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) | |
Defined in Ouroboros.Consensus.Shelley.ShelleyHFC | |
type Rep (ShelleyTip proto era) Source # | |
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
|
Instances
Instances
castShelleyTip :: HeaderHash (ShelleyBlock proto era) ~ HeaderHash (ShelleyBlock proto' era') => ShelleyTip proto era -> ShelleyTip proto' era' Source #
shelleyLedgerTipPoint :: LedgerState (ShelleyBlock proto era) -> Point (ShelleyBlock proto era) Source #
shelleyTipToPoint :: WithOrigin (ShelleyTip proto era) -> Point (ShelleyBlock proto era) Source #
Ledger config
data ShelleyLedgerConfig era Source #
Constructors
ShelleyLedgerConfig | |
Fields
|
Instances
mkShelleyLedgerConfig :: ShelleyGenesis (EraCrypto era) -> TranslationContext era -> EpochInfo (Except PastHorizonException) -> MaxMajorProtVer -> ShelleyLedgerConfig era Source #
shelleyEraParams :: ShelleyGenesis c -> EraParams Source #
shelleyEraParamsNeverHardForks :: ShelleyGenesis c -> EraParams Source #
Separate variant of shelleyEraParams
to be used for a Shelley-only chain.
shelleyLedgerGenesis :: ShelleyLedgerConfig era -> ShelleyGenesis (EraCrypto era) Source #
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 |
data ShelleyReapplyException Source #
Constructors
forall era.Show (BlockTransitionError era) => ShelleyReapplyException (BlockTransitionError era) |
Instances
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 #
encodeShelleyLedgerState :: ShelleyCompatible proto era => LedgerState (ShelleyBlock proto era) -> Encoding Source #
Orphan instances
Generic (LedgerState (ShelleyBlock proto era)) Source # | |
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 # | |
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 # | |
Methods showsPrec :: Int -> LedgerState (ShelleyBlock proto era) -> ShowS Source # show :: LedgerState (ShelleyBlock proto era) -> String Source # showList :: [LedgerState (ShelleyBlock proto era)] -> ShowS Source # | |
ShelleyBasedEra era => Eq (LedgerState (ShelleyBlock proto era)) Source # | |
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 # | |
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 # | |
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 # | |
Methods getTip :: LedgerState (ShelleyBlock proto era) -> Point (LedgerState (ShelleyBlock proto era)) | |
GetTip (Ticked (LedgerState (ShelleyBlock proto era))) Source # | |
Methods getTip :: Ticked (LedgerState (ShelleyBlock proto era)) -> Point (Ticked (LedgerState (ShelleyBlock proto era))) | |
ShelleyBasedEra era => IsLedger (LedgerState (ShelleyBlock proto era)) Source # | |
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 # | |
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 # | |
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 # | |
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 # | |
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 # | |
ShelleyCompatible proto era => CommonProtocolParams (ShelleyBlock proto era) Source # | |
Methods maxHeaderSize :: LedgerState (ShelleyBlock proto era) -> Word32 maxTxSize :: LedgerState (ShelleyBlock proto era) -> Word32 |