Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data ShelleyBBODY era
- data ShelleyBbodyState era = BbodyState !(State (EraRule "LEDGERS" era)) !(BlocksMade (EraCrypto era))
- data BbodyEnv era = BbodyEnv {
- bbodyPp ∷ PParams era
- bbodyAccount ∷ AccountState
- data ShelleyBbodyPredFailure era
- = WrongBlockBodySizeBBODY (Mismatch 'RelEQ Int)
- | InvalidBodyHashBBODY (Mismatch 'RelEQ (Hash (EraCrypto era) EraIndependentBlockBody))
- | LedgersFailure (PredicateFailure (EraRule "LEDGERS" era))
- newtype ShelleyBbodyEvent era = LedgersEvent (Event (EraRule "LEDGERS" era))
- type family PredicateFailure a
- type family State a
- data ShelleyDELEG era
- data DelegEnv era = DelegEnv {
- slotNo ∷ !SlotNo
- curEpochNo ∷ !EpochNo
- ptr_ ∷ !Ptr
- acnt_ ∷ !AccountState
- ppDE ∷ !(PParams era)
- type family PredicateFailure a
- data ShelleyDelegPredFailure era
- = StakeKeyAlreadyRegisteredDELEG !(Credential 'Staking (EraCrypto era))
- | StakeKeyNotRegisteredDELEG !(Credential 'Staking (EraCrypto era))
- | StakeKeyNonZeroAccountBalanceDELEG !Coin
- | StakeDelegationImpossibleDELEG !(Credential 'Staking (EraCrypto era))
- | WrongCertificateTypeDELEG
- | GenesisKeyNotInMappingDELEG !(KeyHash 'Genesis (EraCrypto era))
- | DuplicateGenesisDelegateDELEG !(KeyHash 'GenesisDelegate (EraCrypto era))
- | InsufficientForInstantaneousRewardsDELEG !MIRPot !(Mismatch 'RelLTEQ Coin)
- | MIRCertificateTooLateinEpochDELEG !(Mismatch 'RelLT SlotNo)
- | DuplicateGenesisVRFDELEG !(VRFVerKeyHash 'GenDelegVRF (EraCrypto era))
- | MIRTransferNotCurrentlyAllowed
- | MIRNegativesNotCurrentlyAllowed
- | InsufficientForTransferDELEG !MIRPot !(Mismatch 'RelLTEQ Coin)
- | MIRProducesNegativeUpdate
- | MIRNegativeTransfer !MIRPot !Coin
- newtype ShelleyDelegEvent era = DelegNewEpoch EpochNo
- data ShelleyDELEGS era
- data DelegsEnv era = DelegsEnv {
- delegsSlotNo ∷ !SlotNo
- delegsEpochNo ∷ !EpochNo
- delegsIx ∷ !TxIx
- delegspp ∷ !(PParams era)
- delegsTx ∷ !(Tx era)
- delegsAccount ∷ !AccountState
- data ShelleyDelegsPredFailure era
- = DelegateeNotRegisteredDELEG !(KeyHash 'StakePool (EraCrypto era))
- | WithdrawalsNotInRewardsDELEGS !(Map (RewardAccount (EraCrypto era)) Coin)
- | DelplFailure !(PredicateFailure (EraRule "DELPL" era))
- newtype ShelleyDelegsEvent era = DelplEvent (Event (EraRule "DELPL" era))
- type family PredicateFailure a
- validateZeroRewards ∷ ∀ era. DState era → Withdrawals (EraCrypto era) → Network → Test (Map (RewardAccount (EraCrypto era)) Coin)
- validateStakePoolDelegateeRegistered ∷ PState era → KeyHash 'StakePool (EraCrypto era) → Test (KeyHash 'StakePool (EraCrypto era))
- drainWithdrawals ∷ DState era → Withdrawals (EraCrypto era) → DState era
- data ShelleyDELPL era
- data DelplEnv era = DelplEnv {}
- data ShelleyDelplPredFailure era
- = PoolFailure (PredicateFailure (EraRule "POOL" era))
- | DelegFailure (PredicateFailure (EraRule "DELEG" era))
- data ShelleyDelplEvent era
- type family PredicateFailure a
- data ShelleyLEDGER era
- data LedgerEnv era = LedgerEnv {
- ledgerSlotNo ∷ !SlotNo
- ledgerEpochNo ∷ !(Maybe EpochNo)
- ledgerIx ∷ !TxIx
- ledgerPp ∷ !(PParams era)
- ledgerAccount ∷ !AccountState
- ledgerMempool ∷ !Bool
- data ShelleyLedgerPredFailure era
- = UtxowFailure (PredicateFailure (EraRule "UTXOW" era))
- | DelegsFailure (PredicateFailure (EraRule "DELEGS" era))
- data ShelleyLedgerEvent era
- = UtxowEvent (Event (EraRule "UTXOW" era))
- | DelegsEvent (Event (EraRule "DELEGS" era))
- type family Event a
- type family PredicateFailure a
- epochFromSlot ∷ SlotNo → Reader Globals EpochNo
- renderDepositEqualsObligationViolation ∷ (EraTx era, EraGov era, Environment t ~ LedgerEnv era, Signal t ~ Tx era, State t ~ LedgerState era) ⇒ AssertionViolation t → String
- shelleyLedgerAssertions ∷ (EraGov era, State (rule era) ~ LedgerState era) ⇒ [Assertion (rule era)]
- data ShelleyLEDGERS era
- data ShelleyLedgersEnv era = LedgersEnv {}
- newtype ShelleyLedgersPredFailure era = LedgerFailure (PredicateFailure (EraRule "LEDGER" era))
- newtype ShelleyLedgersEvent era = LedgerEvent (Event (EraRule "LEDGER" era))
- type family PredicateFailure a
- data ShelleyPOOL era
- data PoolEvent era
- = RegisterPool (KeyHash 'StakePool (EraCrypto era))
- | ReregisterPool (KeyHash 'StakePool (EraCrypto era))
- data PoolEnv era = PoolEnv !EpochNo !(PParams era)
- type family PredicateFailure a
- data ShelleyPoolPredFailure era
- = StakePoolNotRegisteredOnKeyPOOL !(KeyHash 'StakePool (EraCrypto era))
- | StakePoolRetirementWrongEpochPOOL !(Mismatch 'RelGT EpochNo) !(Mismatch 'RelLTEQ EpochNo)
- | StakePoolCostTooLowPOOL !(Mismatch 'RelGTEQ Coin)
- | WrongNetworkPOOL !(Mismatch 'RelEQ Network) !(KeyHash 'StakePool (EraCrypto era))
- | PoolMedataHashTooBig !(KeyHash 'StakePool (EraCrypto era)) !Int
- data ShelleyPPUP era
- data PpupEnv era = PPUPEnv SlotNo (PParams era) (GenDelegs (EraCrypto era))
- data ShelleyPpupPredFailure era
- = NonGenesisUpdatePPUP !(Mismatch 'RelSubset (Set (KeyHash 'Genesis (EraCrypto era))))
- | PPUpdateWrongEpoch !EpochNo !EpochNo !VotingPeriod
- | PVCannotFollowPPUP !ProtVer
- data ShelleyGovState era = ShelleyGovState {
- sgsCurProposals ∷ !(ProposedPPUpdates era)
- sgsFutureProposals ∷ !(ProposedPPUpdates era)
- sgsCurPParams ∷ !(PParams era)
- sgsPrevPParams ∷ !(PParams era)
- sgsFuturePParams ∷ !(FuturePParams era)
- newtype PpupEvent era = PpupNewEpoch EpochNo
- type family PredicateFailure a
- data VotingPeriod
- votedFuturePParams ∷ ∀ era. EraPParams era ⇒ ProposedPPUpdates era → PParams era → Word64 → Maybe (PParams era)
- data ShelleyUTXO era
- data UtxoEnv era = UtxoEnv {}
- data ShelleyUtxoPredFailure era
- = BadInputsUTxO !(Set (TxIn (EraCrypto era)))
- | ExpiredUTxO !(Mismatch 'RelLTEQ SlotNo)
- | MaxTxSizeUTxO !(Mismatch 'RelLTEQ Integer)
- | InputSetEmptyUTxO
- | FeeTooSmallUTxO !(Mismatch 'RelGTEQ Coin)
- | ValueNotConservedUTxO !(Mismatch 'RelEQ (Value era))
- | WrongNetwork !Network !(Set (Addr (EraCrypto era)))
- | WrongNetworkWithdrawal !Network !(Set (RewardAccount (EraCrypto era)))
- | OutputTooSmallUTxO ![TxOut era]
- | UpdateFailure (EraRuleFailure "PPUP" era)
- | OutputBootAddrAttrsTooBig ![TxOut era]
- data UtxoEvent era
- = TotalDeposits (SafeHash (EraCrypto era) EraIndependentTxBody) Coin
- | UpdateEvent (Event (EraRule "PPUP" era))
- | TxUTxODiff (UTxO era) (UTxO era)
- type family PredicateFailure a
- updateUTxOState ∷ (EraTxBody era, Monad m) ⇒ PParams era → UTxOState era → TxBody era → CertState era → GovState era → (Coin → m ()) → (UTxO era → UTxO era → m ()) → m (UTxOState era)
- validateInputSetEmptyUTxO ∷ EraTxBody era ⇒ TxBody era → Test (ShelleyUtxoPredFailure era)
- validateFeeTooSmallUTxO ∷ EraUTxO era ⇒ PParams era → Tx era → UTxO era → Test (ShelleyUtxoPredFailure era)
- validateBadInputsUTxO ∷ UTxO era → Set (TxIn (EraCrypto era)) → Test (ShelleyUtxoPredFailure era)
- validateWrongNetwork ∷ (EraTxOut era, Foldable f) ⇒ Network → f (TxOut era) → Test (ShelleyUtxoPredFailure era)
- validateWrongNetworkWithdrawal ∷ EraTxBody era ⇒ Network → TxBody era → Test (ShelleyUtxoPredFailure era)
- validateOutputBootAddrAttrsTooBig ∷ (EraTxOut era, Foldable f) ⇒ f (TxOut era) → Test (ShelleyUtxoPredFailure era)
- validateMaxTxSizeUTxO ∷ EraTx era ⇒ PParams era → Tx era → Test (ShelleyUtxoPredFailure era)
- validateValueNotConservedUTxO ∷ EraUTxO era ⇒ PParams era → UTxO era → CertState era → TxBody era → Test (ShelleyUtxoPredFailure era)
- utxoEnvSlotL ∷ Lens' (UtxoEnv era) SlotNo
- utxoEnvPParamsL ∷ Lens' (UtxoEnv era) (PParams era)
- utxoEnvCertStateL ∷ Lens' (UtxoEnv era) (CertState era)
- data ShelleyUTXOW era
- data ShelleyUtxowPredFailure era
- = InvalidWitnessesUTXOW ![VKey 'Witness (EraCrypto era)]
- | MissingVKeyWitnessesUTXOW !(Set (KeyHash 'Witness (EraCrypto era)))
- | MissingScriptWitnessesUTXOW !(Set (ScriptHash (EraCrypto era)))
- | ScriptWitnessNotValidatingUTXOW !(Set (ScriptHash (EraCrypto era)))
- | UtxoFailure (PredicateFailure (EraRule "UTXO" era))
- | MIRInsufficientGenesisSigsUTXOW (Set (KeyHash 'Witness (EraCrypto era)))
- | MissingTxBodyMetadataHash !(AuxiliaryDataHash (EraCrypto era))
- | MissingTxMetadata !(AuxiliaryDataHash (EraCrypto era))
- | ConflictingMetadataHash !(Mismatch 'RelEQ (AuxiliaryDataHash (EraCrypto era)))
- | InvalidMetadata
- | ExtraneousScriptWitnessesUTXOW !(Set (ScriptHash (EraCrypto era)))
- newtype ShelleyUtxowEvent era = UtxoEvent (Event (EraRule "UTXO" era))
- type family PredicateFailure a
- transitionRulesUTXOW ∷ ∀ era. (EraUTxO era, ShelleyEraTxBody era, ScriptsNeeded era ~ ShelleyScriptsNeeded era, BaseM (EraRule "UTXOW" era) ~ ShelleyBase, Embed (EraRule "UTXO" era) (EraRule "UTXOW" era), Environment (EraRule "UTXO" era) ~ UtxoEnv era, State (EraRule "UTXO" era) ~ UTxOState era, Signal (EraRule "UTXO" era) ~ Tx era, Environment (EraRule "UTXOW" era) ~ UtxoEnv era, State (EraRule "UTXOW" era) ~ UTxOState era, Signal (EraRule "UTXOW" era) ~ Tx era, InjectRuleFailure "UTXOW" ShelleyUtxowPredFailure era, STS (EraRule "UTXOW" era), DSignable (EraCrypto era) (Hash (EraCrypto era) EraIndependentTxBody)) ⇒ TransitionRule (EraRule "UTXOW" era)
- validateFailedNativeScripts ∷ EraTx era ⇒ ScriptsProvided era → Tx era → Test (ShelleyUtxowPredFailure era)
- validateMissingScripts ∷ ShelleyScriptsNeeded era → ScriptsProvided era → Test (ShelleyUtxowPredFailure era)
- validateVerifiedWits ∷ (EraTx era, DSignable (EraCrypto era) (Hash (EraCrypto era) EraIndependentTxBody)) ⇒ Tx era → Test (ShelleyUtxowPredFailure era)
- validateMetadata ∷ EraTx era ⇒ PParams era → Tx era → Test (ShelleyUtxowPredFailure era)
- validateMIRInsufficientGenesisSigs ∷ (EraTx era, ShelleyEraTxBody era) ⇒ GenDelegs (EraCrypto era) → Word64 → Set (KeyHash 'Witness (EraCrypto era)) → Tx era → Test (ShelleyUtxowPredFailure era)
- validateNeededWitnesses ∷ EraUTxO era ⇒ Set (KeyHash 'Witness (EraCrypto era)) → CertState era → UTxO era → TxBody era → Test (ShelleyUtxowPredFailure era)
- data ShelleyEPOCH era
- data ShelleyEpochPredFailure era
- = PoolReapFailure (PredicateFailure (EraRule "POOLREAP" era))
- | SnapFailure (PredicateFailure (EraRule "SNAP" era))
- | UpecFailure (UpecPredFailure era)
- data ShelleyEpochEvent era
- type family PredicateFailure a
- type UpecPredFailure era = UpecPredFailurePV (ProtVerLow era) era
- data ShelleyNEWEPOCH era
- data ShelleyNewEpochPredFailure era
- = EpochFailure (PredicateFailure (EraRule "EPOCH" era))
- | CorruptRewardUpdate !(RewardUpdate (EraCrypto era))
- | MirFailure (PredicateFailure (EraRule "MIR" era))
- data ShelleyNewEpochEvent era
- = DeltaRewardEvent (Event (EraRule "RUPD" era))
- | RestrainedRewards EpochNo (Map (Credential 'Staking (EraCrypto era)) (Set (Reward (EraCrypto era)))) (Set (Credential 'Staking (EraCrypto era)))
- | TotalRewardEvent EpochNo (Map (Credential 'Staking (EraCrypto era)) (Set (Reward (EraCrypto era))))
- | EpochEvent (Event (EraRule "EPOCH" era))
- | MirEvent (Event (EraRule "MIR" era))
- | TotalAdaPotsEvent AdaPots
- type family PredicateFailure a
- updateRewards ∷ EraGov era ⇒ EpochState era → EpochNo → RewardUpdate (EraCrypto era) → Rule (ShelleyNEWEPOCH era) 'Transition (EpochState era)
- calculatePoolDistr ∷ SnapShot c → PoolDistr c
- calculatePoolDistr' ∷ (KeyHash 'StakePool c → Bool) → SnapShot c → PoolDistr c
- data ShelleyRUPD era
- data RupdEnv era = RupdEnv !(BlocksMade (EraCrypto era)) !(EpochState era)
- type family PredicateFailure a
- data ShelleyRupdPredFailure era
- epochInfoRange ∷ Monad m ⇒ EpochInfo m → EpochNo → m (SlotNo, SlotNo)
- data PulsingRewUpdate c
- = Pulsing !(RewardSnapShot c) !(Pulser c)
- | Complete !(RewardUpdate c)
- startStep ∷ ∀ era. EraGov era ⇒ EpochSize → BlocksMade (EraCrypto era) → EpochState era → Coin → ActiveSlotCoeff → Word64 → PulsingRewUpdate (EraCrypto era)
- pulseStep ∷ PulsingRewUpdate c → ShelleyBase (PulsingRewUpdate c, RewardEvent c)
- completeStep ∷ PulsingRewUpdate c → ShelleyBase (PulsingRewUpdate c, RewardEvent c)
- lift ∷ (MonadTrans t, Monad m) ⇒ m a → t m a
- newtype Identity a = Identity {
- runIdentity ∷ a
- data RupdEvent c = RupdEvent !EpochNo !(Map (Credential 'Staking c) (Set (Reward c)))
- data ShelleySNAP era
- type family PredicateFailure a
- data ShelleySnapPredFailure era
- newtype SnapEvent era = StakeDistEvent (Map (Credential 'Staking (EraCrypto era)) (Coin, KeyHash 'StakePool (EraCrypto era)))
- data SnapEnv era = SnapEnv !(LedgerState era) !(PParams era)
- data ShelleyTICK era
- type family State a
- data ShelleyTickPredFailure era
- = NewEpochFailure (PredicateFailure (EraRule "NEWEPOCH" era))
- | RupdFailure (PredicateFailure (EraRule "RUPD" era))
- data ShelleyTickEvent era
- = TickNewEpochEvent (Event (EraRule "NEWEPOCH" era))
- | TickRupdEvent (Event (EraRule "RUPD" era))
- type family PredicateFailure a
- adoptGenesisDelegs ∷ EpochState era → SlotNo → EpochState era
- data ShelleyTICKF era
- data ShelleyTickfPredFailure era
- validatingTickTransition ∷ ∀ tick era. (EraGov era, Embed (EraRule "NEWEPOCH" era) (tick era), STS (tick era), State (tick era) ~ NewEpochState era, BaseM (tick era) ~ ShelleyBase, Environment (EraRule "NEWEPOCH" era) ~ (), State (EraRule "NEWEPOCH" era) ~ NewEpochState era, Signal (EraRule "NEWEPOCH" era) ~ EpochNo) ⇒ NewEpochState era → SlotNo → TransitionRule (tick era)
- validatingTickTransitionFORECAST ∷ ∀ tick era. (State (tick era) ~ NewEpochState era, BaseM (tick era) ~ ShelleyBase, State (EraRule "UPEC" era) ~ UpecState era, Signal (EraRule "UPEC" era) ~ (), Environment (EraRule "UPEC" era) ~ LedgerState era, Embed (EraRule "UPEC" era) (tick era), STS (tick era), GovState era ~ ShelleyGovState era, EraGov era) ⇒ NewEpochState era → SlotNo → TransitionRule (tick era)
- solidifyNextEpochPParams ∷ EraGov era ⇒ NewEpochState era → SlotNo → ShelleyBase (EpochNo, NewEpochState era)
- data ShelleyUPEC era
- data UpecState era = UpecState {
- usCurPParams ∷ !(PParams era)
- usGovState ∷ !(ShelleyGovState era)
- newtype ShelleyUpecPredFailure era = NewPpFailure (PredicateFailure (ShelleyNEWPP era))
- data ShelleyMIR era
- type family PredicateFailure a
- data ShelleyMirPredFailure era
- data ShelleyMirEvent era
- = MirTransfer (InstantaneousRewards (EraCrypto era))
- | NoMirTransfer (InstantaneousRewards (EraCrypto era)) Coin Coin
- emptyInstantaneousRewards ∷ InstantaneousRewards c
- data ShelleyNEWPP era
- data ShelleyNewppState era = NewppState (PParams era) (ShelleyGovState era)
- data NewppEnv era = NewppEnv {
- neCertState ∷ !(CertState era)
- neUTxOState ∷ !(UTxOState era)
- type family PredicateFailure a
- data ShelleyPOOLREAP era
- data ShelleyPoolreapEvent era = RetiredPools {}
- data ShelleyPoolreapState era = PoolreapState {
- prUTxOSt ∷ UTxOState era
- prAccountState ∷ AccountState
- prDState ∷ DState era
- prPState ∷ PState era
- newtype ShelleyPoolreapEnv era = ShelleyPoolreapEnv {}
- type family PredicateFailure a
- data ShelleyPoolreapPredFailure era
Block
data ShelleyBBODY era Source #
Instances
data ShelleyBbodyState era Source #
BbodyState !(State (EraRule "LEDGERS" era)) !(BlocksMade (EraCrypto era)) |
Instances
Show (State (EraRule "LEDGERS" era)) ⇒ Show (ShelleyBbodyState era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
Eq (State (EraRule "LEDGERS" era)) ⇒ Eq (ShelleyBbodyState era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody (==) ∷ ShelleyBbodyState era → ShelleyBbodyState era → Bool Source # (/=) ∷ ShelleyBbodyState era → ShelleyBbodyState era → Bool Source # |
BbodyEnv | |
|
data ShelleyBbodyPredFailure era Source #
WrongBlockBodySizeBBODY (Mismatch 'RelEQ Int) |
|
InvalidBodyHashBBODY (Mismatch 'RelEQ (Hash (EraCrypto era) EraIndependentBlockBody)) |
|
LedgersFailure (PredicateFailure (EraRule "LEDGERS" era)) |
Instances
newtype ShelleyBbodyEvent era Source #
LedgersEvent (Event (EraRule "LEDGERS" era)) |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
Type of the state which the system transitions between.
Instances
data ShelleyDELEG era Source #
Instances
DelegEnv | |
|
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
data ShelleyDelegPredFailure era Source #
Instances
newtype ShelleyDelegEvent era Source #
Instances
Generic (ShelleyDelegEvent era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg from ∷ ShelleyDelegEvent era → Rep (ShelleyDelegEvent era) x Source # to ∷ Rep (ShelleyDelegEvent era) x → ShelleyDelegEvent era Source # | |
NFData (ShelleyDelegEvent era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg rnf ∷ ShelleyDelegEvent era → () Source # | |
Eq (ShelleyDelegEvent era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg (==) ∷ ShelleyDelegEvent era → ShelleyDelegEvent era → Bool Source # (/=) ∷ ShelleyDelegEvent era → ShelleyDelegEvent era → Bool Source # | |
type Rep (ShelleyDelegEvent era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg type Rep (ShelleyDelegEvent era) = D1 ('MetaData "ShelleyDelegEvent" "Cardano.Ledger.Shelley.Rules.Deleg" "cardano-ledger-shelley-1.15.0.0-inplace" 'True) (C1 ('MetaCons "DelegNewEpoch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochNo))) |
data ShelleyDELEGS era Source #
Instances
DelegsEnv | |
|
data ShelleyDelegsPredFailure era Source #
DelegateeNotRegisteredDELEG !(KeyHash 'StakePool (EraCrypto era)) | Target pool which is not registered |
WithdrawalsNotInRewardsDELEGS !(Map (RewardAccount (EraCrypto era)) Coin) | Withdrawals that are missing or do not withdrawal the entire amount |
DelplFailure !(PredicateFailure (EraRule "DELPL" era)) | Subtransition Failures |
Instances
newtype ShelleyDelegsEvent era Source #
DelplEvent (Event (EraRule "DELPL" era)) |
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
validateZeroRewards ∷ ∀ era. DState era → Withdrawals (EraCrypto era) → Network → Test (Map (RewardAccount (EraCrypto era)) Coin) Source #
validateStakePoolDelegateeRegistered ∷ PState era → KeyHash 'StakePool (EraCrypto era) → Test (KeyHash 'StakePool (EraCrypto era)) Source #
drainWithdrawals ∷ DState era → Withdrawals (EraCrypto era) → DState era Source #
data ShelleyDELPL era Source #
Instances
DelplEnv | |
|
data ShelleyDelplPredFailure era Source #
PoolFailure (PredicateFailure (EraRule "POOL" era)) | |
DelegFailure (PredicateFailure (EraRule "DELEG" era)) |
Instances
data ShelleyDelplEvent era Source #
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
data ShelleyLEDGER era Source #
Instances
LedgerEnv | |
|
Instances
data ShelleyLedgerPredFailure era Source #
UtxowFailure (PredicateFailure (EraRule "UTXOW" era)) | |
DelegsFailure (PredicateFailure (EraRule "DELEGS" era)) |
Instances
data ShelleyLedgerEvent era Source #
UtxowEvent (Event (EraRule "UTXOW" era)) | |
DelegsEvent (Event (EraRule "DELEGS" era)) |
Instances
Event type.
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
renderDepositEqualsObligationViolation ∷ (EraTx era, EraGov era, Environment t ~ LedgerEnv era, Signal t ~ Tx era, State t ~ LedgerState era) ⇒ AssertionViolation t → String Source #
shelleyLedgerAssertions ∷ (EraGov era, State (rule era) ~ LedgerState era) ⇒ [Assertion (rule era)] Source #
data ShelleyLEDGERS era Source #
Instances
data ShelleyLedgersEnv era Source #
Instances
newtype ShelleyLedgersPredFailure era Source #
LedgerFailure (PredicateFailure (EraRule "LEDGER" era)) |
Instances
newtype ShelleyLedgersEvent era Source #
LedgerEvent (Event (EraRule "LEDGER" era)) |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
data ShelleyPOOL era Source #
Instances
RegisterPool (KeyHash 'StakePool (EraCrypto era)) | |
ReregisterPool (KeyHash 'StakePool (EraCrypto era)) |
Instances
Generic (PoolEvent era) Source # | |
NFData (PoolEvent era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
Eq (PoolEvent era) Source # | |
type Rep (PoolEvent era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool type Rep (PoolEvent era) = D1 ('MetaData "PoolEvent" "Cardano.Ledger.Shelley.Rules.Pool" "cardano-ledger-shelley-1.15.0.0-inplace" 'False) (C1 ('MetaCons "RegisterPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'StakePool (EraCrypto era)))) :+: C1 ('MetaCons "ReregisterPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'StakePool (EraCrypto era))))) |
Instances
Generic (PoolEnv era) Source # | |
Show (PParams era) ⇒ Show (PoolEnv era) Source # | |
EraPParams era ⇒ EncCBOR (PoolEnv era) Source # | |
NFData (PParams era) ⇒ NFData (PoolEnv era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
Eq (PParams era) ⇒ Eq (PoolEnv era) Source # | |
type Rep (PoolEnv era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool type Rep (PoolEnv era) = D1 ('MetaData "PoolEnv" "Cardano.Ledger.Shelley.Rules.Pool" "cardano-ledger-shelley-1.15.0.0-inplace" 'False) (C1 ('MetaCons "PoolEnv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EpochNo) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PParams era)))) |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
data ShelleyPoolPredFailure era Source #
StakePoolNotRegisteredOnKeyPOOL !(KeyHash 'StakePool (EraCrypto era)) | |
StakePoolRetirementWrongEpochPOOL !(Mismatch 'RelGT EpochNo) !(Mismatch 'RelLTEQ EpochNo) | |
StakePoolCostTooLowPOOL !(Mismatch 'RelGTEQ Coin) | |
WrongNetworkPOOL !(Mismatch 'RelEQ Network) !(KeyHash 'StakePool (EraCrypto era)) | |
PoolMedataHashTooBig !(KeyHash 'StakePool (EraCrypto era)) !Int |
Instances
data ShelleyPPUP era Source #
Instances
data ShelleyPpupPredFailure era Source #
NonGenesisUpdatePPUP !(Mismatch 'RelSubset (Set (KeyHash 'Genesis (EraCrypto era)))) | An update was proposed by a key hash that is not one of the genesis keys.
|
PPUpdateWrongEpoch !EpochNo !EpochNo !VotingPeriod | An update was proposed for the wrong epoch.
The first |
PVCannotFollowPPUP !ProtVer | An update was proposed which contains an invalid protocol version. New protocol versions must either increase the major number by exactly one and set the minor version to zero, or keep the major version the same and increase the minor version by exactly one. |
Instances
data ShelleyGovState era Source #
ShelleyGovState | |
|
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
data VotingPeriod Source #
Instances
∷ ∀ era. EraPParams era | |
⇒ ProposedPPUpdates era | |
→ PParams era | Protocol parameters to which the change will be applied. |
→ Word64 | Quorum needed to change the protocol parameters. |
→ Maybe (PParams era) |
If at least n
nodes voted to change the same protocol parameters to
the same values, return the given protocol parameters updated to these
values. Here n
is the quorum needed.
data ShelleyUTXO era Source #
Instances
Instances
Generic (UtxoEnv era) Source # | |
Show (PParams era) ⇒ Show (UtxoEnv era) Source # | |
EraPParams era ⇒ DecCBOR (UtxoEnv era) Source # | |
EraPParams era ⇒ EncCBOR (UtxoEnv era) Source # | |
(Era era, NFData (PParams era)) ⇒ NFData (UtxoEnv era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
Eq (PParams era) ⇒ Eq (UtxoEnv era) Source # | |
type Rep (UtxoEnv era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo type Rep (UtxoEnv era) = D1 ('MetaData "UtxoEnv" "Cardano.Ledger.Shelley.Rules.Utxo" "cardano-ledger-shelley-1.15.0.0-inplace" 'False) (C1 ('MetaCons "UtxoEnv" 'PrefixI 'True) (S1 ('MetaSel ('Just "ueSlot") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo) :*: (S1 ('MetaSel ('Just "uePParams") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParams era)) :*: S1 ('MetaSel ('Just "ueCertState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (CertState era))))) |
data ShelleyUtxoPredFailure era Source #
BadInputsUTxO !(Set (TxIn (EraCrypto era))) | |
ExpiredUTxO !(Mismatch 'RelLTEQ SlotNo) | |
MaxTxSizeUTxO !(Mismatch 'RelLTEQ Integer) | |
InputSetEmptyUTxO | |
FeeTooSmallUTxO !(Mismatch 'RelGTEQ Coin) | |
ValueNotConservedUTxO !(Mismatch 'RelEQ (Value era)) | |
WrongNetwork !Network !(Set (Addr (EraCrypto era))) | |
WrongNetworkWithdrawal !Network !(Set (RewardAccount (EraCrypto era))) | |
OutputTooSmallUTxO ![TxOut era] | |
UpdateFailure (EraRuleFailure "PPUP" era) | |
OutputBootAddrAttrsTooBig ![TxOut era] |
Instances
TotalDeposits (SafeHash (EraCrypto era) EraIndependentTxBody) Coin | |
UpdateEvent (Event (EraRule "PPUP" era)) | |
TxUTxODiff | The UTxOs consumed and created by a signal tx |
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
updateUTxOState ∷ (EraTxBody era, Monad m) ⇒ PParams era → UTxOState era → TxBody era → CertState era → GovState era → (Coin → m ()) → (UTxO era → UTxO era → m ()) → m (UTxOState era) Source #
This monadic action captures the final stages of the UTXO(S) rule. In particular it
applies all of the UTxO related aditions and removals, gathers all of the fees into the
fee pot utxosFees
and updates the utxosDeposited
field. Continuation supplied will
be called on the deposit - refund
change, which is normally used to emit the
TotalDeposits
event.
Validations
validateInputSetEmptyUTxO ∷ EraTxBody era ⇒ TxBody era → Test (ShelleyUtxoPredFailure era) Source #
Ensure that there is at least one input in the TxBody
txins txb ≠ ∅
validateFeeTooSmallUTxO ∷ EraUTxO era ⇒ PParams era → Tx era → UTxO era → Test (ShelleyUtxoPredFailure era) Source #
Ensure that the fee is at least the amount specified by the minfee
minfee pp tx ≤ txfee txb
validateBadInputsUTxO ∷ UTxO era → Set (TxIn (EraCrypto era)) → Test (ShelleyUtxoPredFailure era) Source #
Ensure all transaction inputs are present in UTxO
inputs ⊆ dom utxo
validateWrongNetwork ∷ (EraTxOut era, Foldable f) ⇒ Network → f (TxOut era) → Test (ShelleyUtxoPredFailure era) Source #
Make sure all addresses match the supplied NetworkId
∀(_ → (a, _)) ∈ txouts txb, netId a = NetworkId
validateWrongNetworkWithdrawal ∷ EraTxBody era ⇒ Network → TxBody era → Test (ShelleyUtxoPredFailure era) Source #
Make sure all addresses match the supplied NetworkId
∀(a → ) ∈ txwdrls txb, netId a = NetworkId
validateOutputBootAddrAttrsTooBig ∷ (EraTxOut era, Foldable f) ⇒ f (TxOut era) → Test (ShelleyUtxoPredFailure era) Source #
Bootstrap (i.e. Byron) addresses have variable sized attributes in them. It is important to limit their overall size.
∀ ( _ ↦ (a,_)) ∈ txoutstxb, a ∈ Addrbootstrap → bootstrapAttrsSize a ≤ 64
validateMaxTxSizeUTxO ∷ EraTx era ⇒ PParams era → Tx era → Test (ShelleyUtxoPredFailure era) Source #
Ensure that the size of the transaction does not exceed the maxTxSize
protocol parameter
txsize tx ≤ maxTxSize pp
validateValueNotConservedUTxO ∷ EraUTxO era ⇒ PParams era → UTxO era → CertState era → TxBody era → Test (ShelleyUtxoPredFailure era) Source #
Ensure that value consumed and produced matches up exactly
consumed pp utxo txb = produced pp poolParams txb
data ShelleyUTXOW era Source #
Instances
data ShelleyUtxowPredFailure era Source #
InvalidWitnessesUTXOW ![VKey 'Witness (EraCrypto era)] | |
MissingVKeyWitnessesUTXOW !(Set (KeyHash 'Witness (EraCrypto era))) | |
MissingScriptWitnessesUTXOW !(Set (ScriptHash (EraCrypto era))) | |
ScriptWitnessNotValidatingUTXOW !(Set (ScriptHash (EraCrypto era))) | |
UtxoFailure (PredicateFailure (EraRule "UTXO" era)) | |
MIRInsufficientGenesisSigsUTXOW (Set (KeyHash 'Witness (EraCrypto era))) | |
MissingTxBodyMetadataHash !(AuxiliaryDataHash (EraCrypto era)) | |
MissingTxMetadata !(AuxiliaryDataHash (EraCrypto era)) | |
ConflictingMetadataHash !(Mismatch 'RelEQ (AuxiliaryDataHash (EraCrypto era))) | |
InvalidMetadata | |
ExtraneousScriptWitnessesUTXOW !(Set (ScriptHash (EraCrypto era))) |
Instances
newtype ShelleyUtxowEvent era Source #
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
transitionRulesUTXOW ∷ ∀ era. (EraUTxO era, ShelleyEraTxBody era, ScriptsNeeded era ~ ShelleyScriptsNeeded era, BaseM (EraRule "UTXOW" era) ~ ShelleyBase, Embed (EraRule "UTXO" era) (EraRule "UTXOW" era), Environment (EraRule "UTXO" era) ~ UtxoEnv era, State (EraRule "UTXO" era) ~ UTxOState era, Signal (EraRule "UTXO" era) ~ Tx era, Environment (EraRule "UTXOW" era) ~ UtxoEnv era, State (EraRule "UTXOW" era) ~ UTxOState era, Signal (EraRule "UTXOW" era) ~ Tx era, InjectRuleFailure "UTXOW" ShelleyUtxowPredFailure era, STS (EraRule "UTXOW" era), DSignable (EraCrypto era) (Hash (EraCrypto era) EraIndependentTxBody)) ⇒ TransitionRule (EraRule "UTXOW" era) Source #
A generic Utxow witnessing function designed to be used across many Eras.
Note the embed
argument lifts from the simple Shelley (ShelleyUtxowPredFailure) to
the PredicateFailure (type family) of the context of where it is called.
Individual validation steps
validateFailedNativeScripts ∷ EraTx era ⇒ ScriptsProvided era → Tx era → Test (ShelleyUtxowPredFailure era) Source #
validateMissingScripts ∷ ShelleyScriptsNeeded era → ScriptsProvided era → Test (ShelleyUtxowPredFailure era) Source #
validateVerifiedWits ∷ (EraTx era, DSignable (EraCrypto era) (Hash (EraCrypto era) EraIndependentTxBody)) ⇒ Tx era → Test (ShelleyUtxowPredFailure era) Source #
Determine if the UTxO witnesses in a given transaction are correct.
validateMetadata ∷ EraTx era ⇒ PParams era → Tx era → Test (ShelleyUtxowPredFailure era) Source #
check metadata hash ((adh = ◇) ∧ (ad= ◇)) ∨ (adh = hashAD ad)
validateMIRInsufficientGenesisSigs ∷ (EraTx era, ShelleyEraTxBody era) ⇒ GenDelegs (EraCrypto era) → Word64 → Set (KeyHash 'Witness (EraCrypto era)) → Tx era → Test (ShelleyUtxowPredFailure era) Source #
check genesis keys signatures for instantaneous rewards certificates
genSig := { hashKey gkey | gkey ∈ dom(genDelegs)} ∩ witsKeyHashes { c ∈ txcerts txb ∩ TxCert_mir} ≠ ∅ ⇒ |genSig| ≥ Quorum
validateNeededWitnesses Source #
∷ EraUTxO era | |
⇒ Set (KeyHash 'Witness (EraCrypto era)) | Provided witness |
→ CertState era | |
→ UTxO era | |
→ TxBody era | |
→ Test (ShelleyUtxowPredFailure era) |
Verify that we provide at least all of the required witnesses
witsVKeyNeeded utxo tx ⊆ witsKeyHashes
Tick
data ShelleyEPOCH era Source #
Instances
data ShelleyEpochPredFailure era Source #
PoolReapFailure (PredicateFailure (EraRule "POOLREAP" era)) | |
SnapFailure (PredicateFailure (EraRule "SNAP" era)) | |
UpecFailure (UpecPredFailure era) |
Instances
data ShelleyEpochEvent era Source #
PoolReapEvent (Event (EraRule "POOLREAP" era)) | |
SnapEvent (Event (EraRule "SNAP" era)) | |
UpecEvent (Event (EraRule "UPEC" era)) |
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
type UpecPredFailure era = UpecPredFailurePV (ProtVerLow era) era Source #
data ShelleyNEWEPOCH era Source #
Instances
data ShelleyNewEpochPredFailure era Source #
EpochFailure (PredicateFailure (EraRule "EPOCH" era)) | |
CorruptRewardUpdate !(RewardUpdate (EraCrypto era)) | |
MirFailure (PredicateFailure (EraRule "MIR" era)) |
Instances
data ShelleyNewEpochEvent era Source #
DeltaRewardEvent (Event (EraRule "RUPD" era)) | |
RestrainedRewards EpochNo (Map (Credential 'Staking (EraCrypto era)) (Set (Reward (EraCrypto era)))) (Set (Credential 'Staking (EraCrypto era))) | |
TotalRewardEvent EpochNo (Map (Credential 'Staking (EraCrypto era)) (Set (Reward (EraCrypto era)))) | |
EpochEvent (Event (EraRule "EPOCH" era)) | |
MirEvent (Event (EraRule "MIR" era)) | |
TotalAdaPotsEvent AdaPots |
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
updateRewards ∷ EraGov era ⇒ EpochState era → EpochNo → RewardUpdate (EraCrypto era) → Rule (ShelleyNEWEPOCH era) 'Transition (EpochState era) Source #
calculatePoolDistr ∷ SnapShot c → PoolDistr c Source #
data ShelleyRUPD era Source #
Instances
RupdEnv !(BlocksMade (EraCrypto era)) !(EpochState era) |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
data ShelleyRupdPredFailure era Source #
Instances
Generic (ShelleyRupdPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd from ∷ ShelleyRupdPredFailure era → Rep (ShelleyRupdPredFailure era) x Source # to ∷ Rep (ShelleyRupdPredFailure era) x → ShelleyRupdPredFailure era Source # | |
Show (ShelleyRupdPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
NFData (ShelleyRupdPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd rnf ∷ ShelleyRupdPredFailure era → () Source # | |
Eq (ShelleyRupdPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd (==) ∷ ShelleyRupdPredFailure era → ShelleyRupdPredFailure era → Bool Source # (/=) ∷ ShelleyRupdPredFailure era → ShelleyRupdPredFailure era → Bool Source # | |
NoThunks (ShelleyRupdPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
type Rep (ShelleyRupdPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd |
data PulsingRewUpdate c Source #
The state used in the STS rules
Pulsing !(RewardSnapShot c) !(Pulser c) | |
Complete !(RewardUpdate c) |
Instances
startStep ∷ ∀ era. EraGov era ⇒ EpochSize → BlocksMade (EraCrypto era) → EpochState era → Coin → ActiveSlotCoeff → Word64 → PulsingRewUpdate (EraCrypto era) Source #
pulseStep ∷ PulsingRewUpdate c → ShelleyBase (PulsingRewUpdate c, RewardEvent c) Source #
Run the pulser for a bit. If is has nothing left to do, complete it.
completeStep ∷ PulsingRewUpdate c → ShelleyBase (PulsingRewUpdate c, RewardEvent c) Source #
lift ∷ (MonadTrans t, Monad m) ⇒ m a → t m a Source #
Lift a computation from the argument monad to the constructed monad.
Identity functor and monad. (a non-strict monad)
Since: base-4.8.0.0
Identity | |
|
Instances
Instances
Generic (RupdEvent c) Source # | |
NFData (RupdEvent c) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
Eq (RupdEvent c) Source # | |
type Rep (RupdEvent c) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd type Rep (RupdEvent c) = D1 ('MetaData "RupdEvent" "Cardano.Ledger.Shelley.Rules.Rupd" "cardano-ledger-shelley-1.15.0.0-inplace" 'False) (C1 ('MetaCons "RupdEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EpochNo) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'Staking c) (Set (Reward c)))))) |
data ShelleySNAP era Source #
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
data ShelleySnapPredFailure era Source #
Instances
Generic (ShelleySnapPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap from ∷ ShelleySnapPredFailure era → Rep (ShelleySnapPredFailure era) x Source # to ∷ Rep (ShelleySnapPredFailure era) x → ShelleySnapPredFailure era Source # | |
Show (ShelleySnapPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
NFData (ShelleySnapPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap rnf ∷ ShelleySnapPredFailure era → () Source # | |
Eq (ShelleySnapPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap (==) ∷ ShelleySnapPredFailure era → ShelleySnapPredFailure era → Bool Source # (/=) ∷ ShelleySnapPredFailure era → ShelleySnapPredFailure era → Bool Source # | |
NoThunks (ShelleySnapPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
type Rep (ShelleySnapPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap |
newtype SnapEvent era Source #
StakeDistEvent (Map (Credential 'Staking (EraCrypto era)) (Coin, KeyHash 'StakePool (EraCrypto era))) |
Instances
Generic (SnapEvent era) Source # | |
NFData (SnapEvent era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
Eq (SnapEvent era) Source # | |
type Rep (SnapEvent era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap type Rep (SnapEvent era) = D1 ('MetaData "SnapEvent" "Cardano.Ledger.Shelley.Rules.Snap" "cardano-ledger-shelley-1.15.0.0-inplace" 'True) (C1 ('MetaCons "StakeDistEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (Credential 'Staking (EraCrypto era)) (Coin, KeyHash 'StakePool (EraCrypto era)))))) |
data ShelleyTICK era Source #
Instances
Type of the state which the system transitions between.
Instances
data ShelleyTickPredFailure era Source #
NewEpochFailure (PredicateFailure (EraRule "NEWEPOCH" era)) | |
RupdFailure (PredicateFailure (EraRule "RUPD" era)) |
Instances
data ShelleyTickEvent era Source #
TickNewEpochEvent (Event (EraRule "NEWEPOCH" era)) | |
TickRupdEvent (Event (EraRule "RUPD" era)) |
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
adoptGenesisDelegs ∷ EpochState era → SlotNo → EpochState era Source #
data ShelleyTICKF era Source #
Instances
data ShelleyTickfPredFailure era Source #
Instances
validatingTickTransition ∷ ∀ tick era. (EraGov era, Embed (EraRule "NEWEPOCH" era) (tick era), STS (tick era), State (tick era) ~ NewEpochState era, BaseM (tick era) ~ ShelleyBase, Environment (EraRule "NEWEPOCH" era) ~ (), State (EraRule "NEWEPOCH" era) ~ NewEpochState era, Signal (EraRule "NEWEPOCH" era) ~ EpochNo) ⇒ NewEpochState era → SlotNo → TransitionRule (tick era) Source #
This is a limited version of bheadTransition
which is suitable for the
future ledger view.
validatingTickTransitionFORECAST ∷ ∀ tick era. (State (tick era) ~ NewEpochState era, BaseM (tick era) ~ ShelleyBase, State (EraRule "UPEC" era) ~ UpecState era, Signal (EraRule "UPEC" era) ~ (), Environment (EraRule "UPEC" era) ~ LedgerState era, Embed (EraRule "UPEC" era) (tick era), STS (tick era), GovState era ~ ShelleyGovState era, EraGov era) ⇒ NewEpochState era → SlotNo → TransitionRule (tick era) Source #
This is a limited version of validatingTickTransition
which is only suitable
for the future ledger view.
solidifyNextEpochPParams ∷ EraGov era ⇒ NewEpochState era → SlotNo → ShelleyBase (EpochNo, NewEpochState era) Source #
This action ensures that once the current slot number is at the point of no return we mark the future PParams to be updated at the next epoch boundary. Also returns the current epoch number for convenience.
data ShelleyUPEC era Source #
Instances
UpecState | |
|
newtype ShelleyUpecPredFailure era Source #
NewPpFailure (PredicateFailure (ShelleyNEWPP era)) |
Instances
data ShelleyMIR era Source #
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
data ShelleyMirPredFailure era Source #
Instances
Generic (ShelleyMirPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir from ∷ ShelleyMirPredFailure era → Rep (ShelleyMirPredFailure era) x Source # to ∷ Rep (ShelleyMirPredFailure era) x → ShelleyMirPredFailure era Source # | |
Show (ShelleyMirPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
NFData (ShelleyMirPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir rnf ∷ ShelleyMirPredFailure era → () Source # | |
Eq (ShelleyMirPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir (==) ∷ ShelleyMirPredFailure era → ShelleyMirPredFailure era → Bool Source # (/=) ∷ ShelleyMirPredFailure era → ShelleyMirPredFailure era → Bool Source # | |
NoThunks (ShelleyMirPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
type Rep (ShelleyMirPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir |
data ShelleyMirEvent era Source #
MirTransfer (InstantaneousRewards (EraCrypto era)) | |
NoMirTransfer (InstantaneousRewards (EraCrypto era)) Coin Coin | We were not able to perform an MIR transfer due to insufficient funds. This event gives the rewards we wanted to pay, plus the available reserves and treasury. |
Instances
data ShelleyNEWPP era Source #
Instances
data ShelleyNewppState era Source #
NewppState (PParams era) (ShelleyGovState era) |
Instances
EraPParams era ⇒ Default (ShelleyNewppState era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp def ∷ ShelleyNewppState era Source # |
NewppEnv | |
|
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
data ShelleyPOOLREAP era Source #
Instances
data ShelleyPoolreapEvent era Source #
Instances
data ShelleyPoolreapState era Source #
PoolreapState | |
|
Instances
Show (UTxOState era) ⇒ Show (ShelleyPoolreapState era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
Default (UTxOState era) ⇒ Default (ShelleyPoolreapState era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap def ∷ ShelleyPoolreapState era Source # |
newtype ShelleyPoolreapEnv era Source #
Instances
Show (PParams era) ⇒ Show (ShelleyPoolreapEnv era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
Eq (PParams era) ⇒ Eq (ShelleyPoolreapEnv era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap (==) ∷ ShelleyPoolreapEnv era → ShelleyPoolreapEnv era → Bool Source # (/=) ∷ ShelleyPoolreapEnv era → ShelleyPoolreapEnv era → Bool Source # |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailure
s which are "structural" (meaning that
they are not "throwable" in practice, and are used to pass control from
one transition rule to another) are prefixed with S_
.
Structural PredicateFailure
s represent conditions between rules where
the disjunction of all rules' preconditions is equal to True
. That is,
either one rule will throw a structural PredicateFailure
and the other
will succeed, or vice-versa.
Instances
data ShelleyPoolreapPredFailure era Source #
Instances
Generic (ShelleyPoolreapPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap from ∷ ShelleyPoolreapPredFailure era → Rep (ShelleyPoolreapPredFailure era) x Source # to ∷ Rep (ShelleyPoolreapPredFailure era) x → ShelleyPoolreapPredFailure era Source # | |
Show (ShelleyPoolreapPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
NFData (ShelleyPoolreapPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap rnf ∷ ShelleyPoolreapPredFailure era → () Source # | |
Eq (ShelleyPoolreapPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap (==) ∷ ShelleyPoolreapPredFailure era → ShelleyPoolreapPredFailure era → Bool Source # (/=) ∷ ShelleyPoolreapPredFailure era → ShelleyPoolreapPredFailure era → Bool Source # | |
NoThunks (ShelleyPoolreapPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
type Rep (ShelleyPoolreapPredFailure era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap |