ouroboros-consensus-cardano-0.12.1.0: The instantation of the Ouroboros consensus layer used by Cardano
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Consensus.Cardano.CanHardFork

Synopsis

Documentation

data ByronPartialLedgerConfig Source #

When Byron is part of the hard-fork combinator, we use the partial ledger config. Standalone Byron uses the regular ledger config. This means that the partial ledger config is the perfect place to store the trigger condition for the hard fork to Shelley, as we don't have to modify the ledger config for standalone Byron.

Instances

Instances details
Generic ByronPartialLedgerConfig Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.CanHardFork

Associated Types

type Rep ByronPartialLedgerConfig :: Type -> Type Source #

NoThunks ByronPartialLedgerConfig Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.CanHardFork

type Rep ByronPartialLedgerConfig Source # 
Instance details

Defined in Ouroboros.Consensus.Cardano.CanHardFork

type Rep ByronPartialLedgerConfig = D1 ('MetaData "ByronPartialLedgerConfig" "Ouroboros.Consensus.Cardano.CanHardFork" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ByronPartialLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "byronLedgerConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (LedgerConfig ByronBlock)) :*: S1 ('MetaSel ('Just "byronTriggerHardFork") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TriggerHardFork)))

type CardanoHardForkConstraints c = (PraosCrypto c, PraosCrypto c, TranslateProto (TPraos c) (Praos c), ShelleyCompatible (TPraos c) (ShelleyEra c), LedgerSupportsProtocol (ShelleyBlock (TPraos c) (ShelleyEra c)), ShelleyCompatible (TPraos c) (AllegraEra c), LedgerSupportsProtocol (ShelleyBlock (TPraos c) (AllegraEra c)), ShelleyCompatible (TPraos c) (MaryEra c), LedgerSupportsProtocol (ShelleyBlock (TPraos c) (MaryEra c)), ShelleyCompatible (TPraos c) (AlonzoEra c), LedgerSupportsProtocol (ShelleyBlock (TPraos c) (AlonzoEra c)), ShelleyCompatible (Praos c) (BabbageEra c), LedgerSupportsProtocol (ShelleyBlock (Praos c) (BabbageEra c)), ShelleyCompatible (Praos c) (ConwayEra c), LedgerSupportsProtocol (ShelleyBlock (Praos c) (ConwayEra c)), HASH c ~ Blake2b_256, ADDRHASH c ~ Blake2b_224, DSIGN c ~ Ed25519DSIGN) Source #

data TriggerHardFork #

Instances

Instances details
Generic TriggerHardFork 
Instance details

Defined in Ouroboros.Consensus.HardFork.Simple

Associated Types

type Rep TriggerHardFork :: Type -> Type Source #

Show TriggerHardFork 
Instance details

Defined in Ouroboros.Consensus.HardFork.Simple

NoThunks TriggerHardFork 
Instance details

Defined in Ouroboros.Consensus.HardFork.Simple

Methods

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

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

showTypeOf :: Proxy TriggerHardFork -> String

type Rep TriggerHardFork 
Instance details

Defined in Ouroboros.Consensus.HardFork.Simple

type Rep TriggerHardFork = D1 ('MetaData "TriggerHardFork" "Ouroboros.Consensus.HardFork.Simple" "ouroboros-consensus-0.14.0.0-121Znn1OCbJFCod8haNyF" 'False) (C1 ('MetaCons "TriggerHardForkAtVersion" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Word16)) :+: (C1 ('MetaCons "TriggerHardForkAtEpoch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo)) :+: C1 ('MetaCons "TriggerHardForkNotDuringThisExecution" 'PrefixI 'False) (U1 :: Type -> Type)))

Re-exports of Shelley code

data ShelleyPartialLedgerConfig era Source #

Constructors

ShelleyPartialLedgerConfig 

Fields

Instances

Instances details
Generic (ShelleyPartialLedgerConfig era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Associated Types

type Rep (ShelleyPartialLedgerConfig era) :: Type -> Type Source #

(NoThunks (TranslationContext era), Era era) => NoThunks (ShelleyPartialLedgerConfig era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

Methods

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

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

showTypeOf :: Proxy (ShelleyPartialLedgerConfig era) -> String

type Rep (ShelleyPartialLedgerConfig era) Source # 
Instance details

Defined in Ouroboros.Consensus.Shelley.ShelleyHFC

type Rep (ShelleyPartialLedgerConfig era) = D1 ('MetaData "ShelleyPartialLedgerConfig" "Ouroboros.Consensus.Shelley.ShelleyHFC" "ouroboros-consensus-cardano-0.12.1.0-B7PPTiiOqdjFK3zhRUwDA9" 'False) (C1 ('MetaCons "ShelleyPartialLedgerConfig" 'PrefixI 'True) (S1 ('MetaSel ('Just "shelleyLedgerConfig") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ShelleyLedgerConfig era)) :*: S1 ('MetaSel ('Just "shelleyTriggerHardFork") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 TriggerHardFork)))

forecastAcrossShelley Source #

Arguments

:: forall protoFrom protoTo eraFrom eraTo. (TranslateProto protoFrom protoTo, LedgerSupportsProtocol (ShelleyBlock protoFrom eraFrom)) 
=> ShelleyLedgerConfig eraFrom 
-> ShelleyLedgerConfig eraTo 
-> Bound

Transition between the two eras

-> SlotNo

Forecast for this slot

-> LedgerState (ShelleyBlock protoFrom eraFrom) 
-> Except OutsideForecastRange (WrapLedgerView (ShelleyBlock protoTo eraTo)) 

Forecast from a Shelley-based era to the next Shelley-based era.

translateChainDepStateAcrossShelley :: forall eraFrom eraTo protoFrom protoTo. TranslateProto protoFrom protoTo => RequiringBoth WrapConsensusConfig (Translate WrapChainDepState) (ShelleyBlock protoFrom eraFrom) (ShelleyBlock protoTo eraTo) Source #

Orphan instances

SingleEraBlock ByronBlock Source # 
Instance details

Methods

singleEraTransition :: PartialLedgerConfig ByronBlock -> EraParams -> Bound -> LedgerState ByronBlock -> Maybe EpochNo

singleEraInfo :: proxy ByronBlock -> SingleEraInfo ByronBlock

HasPartialLedgerConfig ByronBlock Source # 
Instance details

Associated Types

type PartialLedgerConfig ByronBlock

Methods

completeLedgerConfig :: proxy ByronBlock -> EpochInfo (Except PastHorizonException) -> PartialLedgerConfig ByronBlock -> LedgerConfig ByronBlock

CardanoHardForkConstraints c => CanHardFork (CardanoEras c) Source # 
Instance details

Methods

hardForkEraTranslation :: EraTranslation (CardanoEras c)

hardForkChainSel :: Tails AcrossEraSelection (CardanoEras c)

hardForkInjectTxs :: InPairs (RequiringBoth WrapLedgerConfig (Product2 InjectTx InjectValidatedTx)) (CardanoEras c)

PBftCrypto bc => HasPartialConsensusConfig (PBft bc) Source # 
Instance details

Associated Types

type PartialConsensusConfig (PBft bc)

Methods

completeConsensusConfig :: proxy (PBft bc) -> EpochInfo (Except PastHorizonException) -> PartialConsensusConfig (PBft bc) -> ConsensusConfig (PBft bc)

toPartialConsensusConfig :: proxy (PBft bc) -> ConsensusConfig (PBft bc) -> PartialConsensusConfig (PBft bc)