| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Cardano.Ledger.Shelley.Rules
Synopsis
- type family State a
- type family PredicateFailure a
- type family State a
- type family PredicateFailure a
- data ShelleyBBODY era
- data ShelleyBbodyState era = BbodyState !(State (EraRule "LEDGERS" era)) !BlocksMade
- data BbodyEnv era = BbodyEnv {}
- data ShelleyBbodyPredFailure era
- = WrongBlockBodySizeBBODY (Mismatch 'RelEQ Int)
- | InvalidBodyHashBBODY (Mismatch 'RelEQ (Hash HASH EraIndependentBlockBody))
- | LedgersFailure (PredicateFailure (EraRule "LEDGERS" era))
- newtype ShelleyBbodyEvent era = LedgersEvent (Event (EraRule "LEDGERS" era))
- type family PredicateFailure a
- type family PredicateFailure a
- data DelegEnv era = DelegEnv {}
- data ShelleyDELEG era
- data ShelleyDelegPredFailure era
- = StakeKeyAlreadyRegisteredDELEG (Credential 'Staking)
- | StakeKeyNotRegisteredDELEG (Credential 'Staking)
- | StakeKeyNonZeroAccountBalanceDELEG Coin
- | StakeDelegationImpossibleDELEG (Credential 'Staking)
- | WrongCertificateTypeDELEG
- | GenesisKeyNotInMappingDELEG (KeyHash 'GenesisRole)
- | DuplicateGenesisDelegateDELEG (KeyHash 'GenesisDelegate)
- | InsufficientForInstantaneousRewardsDELEG MIRPot (Mismatch 'RelLTEQ Coin)
- | MIRCertificateTooLateinEpochDELEG (Mismatch 'RelLT SlotNo)
- | DuplicateGenesisVRFDELEG (VRFVerKeyHash 'GenDelegVRF)
- | MIRTransferNotCurrentlyAllowed
- | MIRNegativesNotCurrentlyAllowed
- | InsufficientForTransferDELEG MIRPot (Mismatch 'RelLTEQ Coin)
- | MIRProducesNegativeUpdate
- | MIRNegativeTransfer MIRPot Coin
- newtype ShelleyDelegEvent era = DelegNewEpoch EpochNo
- type family PredicateFailure a
- type family PredicateFailure a
- data DelegsEnv era = DelegsEnv {
- delegsSlotNo ∷ SlotNo
- delegsEpochNo ∷ EpochNo
- delegsIx ∷ TxIx
- delegspp ∷ PParams era
- delegsTx ∷ Tx 'TopTx era
- delegsAccount ∷ ChainAccountState
- data ShelleyDELEGS era
- data ShelleyDelegsPredFailure era
- = DelegateeNotRegisteredDELEG (KeyHash 'StakePool)
- | DelplFailure (PredicateFailure (EraRule "DELPL" era))
- newtype ShelleyDelegsEvent era = DelplEvent (Event (EraRule "DELPL" era))
- validateStakePoolDelegateeRegistered ∷ PState era → KeyHash 'StakePool → Test (KeyHash 'StakePool)
- type family PredicateFailure a
- type family PredicateFailure a
- data DelplEnv era = DelplEnv {}
- data ShelleyDELPL era
- data ShelleyDelplPredFailure era
- = PoolFailure (PredicateFailure (EraRule "POOL" era))
- | DelegFailure (PredicateFailure (EraRule "DELEG" era))
- data ShelleyDelplEvent era
- type family Event a
- type family PredicateFailure a
- type family Event a
- epochFromSlot ∷ SlotNo → Reader Globals EpochNo
- type family PredicateFailure a
- data LedgerEnv era = LedgerEnv {}
- data ShelleyLEDGER era
- data ShelleyLedgerPredFailure era
- = UtxowFailure (PredicateFailure (EraRule "UTXOW" era))
- | DelegsFailure (PredicateFailure (EraRule "DELEGS" era))
- | ShelleyWithdrawalsMissingAccounts Withdrawals
- | ShelleyIncompleteWithdrawals Withdrawals
- ledgerSlotNoL ∷ ∀ era f. Functor f ⇒ (SlotNo → f SlotNo) → LedgerEnv era → f (LedgerEnv era)
- ledgerEpochNoL ∷ ∀ era f. Functor f ⇒ (Maybe EpochNo → f (Maybe EpochNo)) → LedgerEnv era → f (LedgerEnv era)
- ledgerIxL ∷ ∀ era f. Functor f ⇒ (TxIx → f TxIx) → LedgerEnv era → f (LedgerEnv era)
- ledgerPpL ∷ ∀ era f. Functor f ⇒ (PParams era → f (PParams era)) → LedgerEnv era → f (LedgerEnv era)
- ledgerAccountL ∷ ∀ era f. Functor f ⇒ (ChainAccountState → f ChainAccountState) → LedgerEnv era → f (LedgerEnv era)
- data ShelleyLedgerEvent era
- = UtxowEvent (Event (EraRule "UTXOW" era))
- | DelegsEvent (Event (EraRule "DELEGS" era))
- renderDepositEqualsObligationViolation ∷ (EraTx era, EraGov era, EraCertState era, Environment t ~ LedgerEnv era, Signal t ~ Tx 'TopTx era, State t ~ LedgerState era) ⇒ AssertionViolation t → String
- shelleyLedgerAssertions ∷ (EraGov era, EraCertState era, State (rule era) ~ LedgerState era) ⇒ [Assertion (rule era)]
- testIncompleteAndMissingWithdrawals ∷ ∀ era sts (ctx ∷ RuleType). (EraAccounts era, STS sts, BaseM sts ~ ShelleyBase, InjectRuleFailure "LEDGER" ShelleyLedgerPredFailure era, sts ~ EraRule "LEDGER" era) ⇒ Accounts era → Withdrawals → Rule sts ctx ()
- type family PredicateFailure a
- type family PredicateFailure a
- 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
- type family PredicateFailure a
- data PoolEnv era = PoolEnv EpochNo (PParams era)
- data ShelleyPOOL era
- data ShelleyPoolPredFailure era
- = StakePoolNotRegisteredOnKeyPOOL (KeyHash 'StakePool)
- | StakePoolRetirementWrongEpochPOOL (Mismatch 'RelGT EpochNo) (Mismatch 'RelLTEQ EpochNo)
- | StakePoolCostTooLowPOOL (Mismatch 'RelGTEQ Coin)
- | WrongNetworkPOOL (Mismatch 'RelEQ Network) (KeyHash 'StakePool)
- | PoolMedataHashTooBig (KeyHash 'StakePool) Int
- | VRFKeyHashAlreadyRegistered (KeyHash 'StakePool) (VRFVerKeyHash 'StakePoolVRF)
- data PoolEvent era
- type family PredicateFailure a
- type family PredicateFailure a
- data ShelleyGovState era = ShelleyGovState {
- sgsCurProposals ∷ !(ProposedPPUpdates era)
- sgsFutureProposals ∷ !(ProposedPPUpdates era)
- sgsCurPParams ∷ !(PParams era)
- sgsPrevPParams ∷ !(PParams era)
- sgsFuturePParams ∷ !(FuturePParams era)
- data PpupEnv era = PPUPEnv SlotNo (PParams era) GenDelegs
- data ShelleyPPUP era
- data ShelleyPpupPredFailure era
- votedFuturePParams ∷ EraPParams era ⇒ ProposedPPUpdates era → PParams era → Word64 → Maybe (PParams era)
- newtype PpupEvent era = PpupNewEpoch EpochNo
- data VotingPeriod
- type family PredicateFailure a
- type family PredicateFailure a
- data ShelleyUTXO era
- data UtxoEnv era = UtxoEnv {}
- data ShelleyUtxoPredFailure era
- = BadInputsUTxO (Set TxIn)
- | ExpiredUTxO (Mismatch 'RelLTEQ SlotNo)
- | MaxTxSizeUTxO (Mismatch 'RelLTEQ Word32)
- | InputSetEmptyUTxO
- | FeeTooSmallUTxO (Mismatch 'RelGTEQ Coin)
- | ValueNotConservedUTxO (Mismatch 'RelEQ (Value era))
- | WrongNetwork Network (Set Addr)
- | WrongNetworkWithdrawal Network (Set RewardAccount)
- | OutputTooSmallUTxO [TxOut era]
- | UpdateFailure (EraRuleFailure "PPUP" era)
- | OutputBootAddrAttrsTooBig [TxOut era]
- data UtxoEvent era
- = TotalDeposits (SafeHash EraIndependentTxBody) Coin
- | UpdateEvent (Event (EraRule "PPUP" era))
- | TxUTxODiff (UTxO era) (UTxO era)
- validSizeComputationCheck ∷ (EraTx era, SafeToHash (TxWits era), Signal (rule era) ~ Tx 'TopTx era) ⇒ Assertion (rule era)
- updateUTxOState ∷ (EraTxBody era, EraStake era, EraCertState era, Monad m) ⇒ PParams era → UTxOState era → TxBody 'TopTx era → CertState era → GovState era → (Coin → m ()) → (UTxO era → UTxO era → m ()) → m (UTxOState era)
- validateInputSetEmptyUTxO ∷ ∀ era (t ∷ TxLevel). EraTxBody era ⇒ TxBody t era → Test (ShelleyUtxoPredFailure era)
- validateFeeTooSmallUTxO ∷ EraUTxO era ⇒ PParams era → Tx 'TopTx era → UTxO era → Test (ShelleyUtxoPredFailure era)
- validateBadInputsUTxO ∷ UTxO era → Set TxIn → Test (ShelleyUtxoPredFailure era)
- validateWrongNetwork ∷ (EraTxOut era, Foldable f) ⇒ Network → f (TxOut era) → Test (ShelleyUtxoPredFailure era)
- validateWrongNetworkWithdrawal ∷ ∀ era (t ∷ TxLevel). EraTxBody era ⇒ Network → TxBody t era → Test (ShelleyUtxoPredFailure era)
- validateOutputBootAddrAttrsTooBig ∷ (EraTxOut era, Foldable f) ⇒ f (TxOut era) → Test (ShelleyUtxoPredFailure era)
- validateMaxTxSizeUTxO ∷ ∀ era (l ∷ TxLevel). EraTx era ⇒ PParams era → Tx l era → Test (ShelleyUtxoPredFailure era)
- validateValueNotConservedUTxO ∷ (EraUTxO era, EraCertState era) ⇒ PParams era → UTxO era → CertState era → TxBody 'TopTx era → Test (ShelleyUtxoPredFailure era)
- utxoEnvSlotL ∷ ∀ era f. Functor f ⇒ (SlotNo → f SlotNo) → UtxoEnv era → f (UtxoEnv era)
- utxoEnvPParamsL ∷ ∀ era f. Functor f ⇒ (PParams era → f (PParams era)) → UtxoEnv era → f (UtxoEnv era)
- utxoEnvCertStateL ∷ ∀ era f. Functor f ⇒ (CertState era → f (CertState era)) → UtxoEnv era → f (UtxoEnv era)
- type family PredicateFailure a
- type family PredicateFailure a
- data ShelleyUTXOW era
- data ShelleyUtxowPredFailure era
- = InvalidWitnessesUTXOW [VKey 'Witness]
- | MissingVKeyWitnessesUTXOW (Set (KeyHash 'Witness))
- | MissingScriptWitnessesUTXOW (Set ScriptHash)
- | ScriptWitnessNotValidatingUTXOW (Set ScriptHash)
- | UtxoFailure (PredicateFailure (EraRule "UTXO" era))
- | MIRInsufficientGenesisSigsUTXOW (Set (KeyHash 'Witness))
- | MissingTxBodyMetadataHash TxAuxDataHash
- | MissingTxMetadata TxAuxDataHash
- | ConflictingMetadataHash (Mismatch 'RelEQ TxAuxDataHash)
- | InvalidMetadata
- | ExtraneousScriptWitnessesUTXOW (Set ScriptHash)
- newtype ShelleyUtxowEvent era = UtxoEvent (Event (EraRule "UTXO" era))
- transitionRulesUTXOW ∷ (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 'TopTx era, Environment (EraRule "UTXOW" era) ~ UtxoEnv era, State (EraRule "UTXOW" era) ~ UTxOState era, Signal (EraRule "UTXOW" era) ~ Tx 'TopTx era, InjectRuleFailure "UTXOW" ShelleyUtxowPredFailure era, STS (EraRule "UTXOW" era), EraCertState era) ⇒ TransitionRule (EraRule "UTXOW" era)
- validateFailedNativeScripts ∷ ∀ era (l ∷ TxLevel). EraTx era ⇒ ScriptsProvided era → Tx l era → Test (ShelleyUtxowPredFailure era)
- validateMissingScripts ∷ ShelleyScriptsNeeded era → ScriptsProvided era → Test (ShelleyUtxowPredFailure era)
- validateVerifiedWits ∷ ∀ era (l ∷ TxLevel). EraTx era ⇒ Tx l era → Test (ShelleyUtxowPredFailure era)
- validateMetadata ∷ ∀ era (l ∷ TxLevel). EraTx era ⇒ PParams era → Tx l era → Test (ShelleyUtxowPredFailure era)
- validateMIRInsufficientGenesisSigs ∷ (EraTx era, ShelleyEraTxBody era) ⇒ GenDelegs → Word64 → Set (KeyHash 'Witness) → Tx 'TopTx era → Test (ShelleyUtxowPredFailure era)
- validateNeededWitnesses ∷ ∀ era (t ∷ TxLevel). EraUTxO era ⇒ Set (KeyHash 'Witness) → CertState era → UTxO era → TxBody t era → Test (ShelleyUtxowPredFailure era)
- type family PredicateFailure a
- type family PredicateFailure a
- data ShelleyEPOCH era
- data ShelleyEpochEvent era
- calculatePoolDistr ∷ SnapShot → PoolDistr
- calculatePoolDistr' ∷ (KeyHash 'StakePool → Bool) → SnapShot → PoolDistr
- type family PredicateFailure a
- type family PredicateFailure a
- data ShelleyNEWEPOCH era
- data ShelleyNewEpochEvent era
- = DeltaRewardEvent (Event (EraRule "RUPD" era))
- | RestrainedRewards EpochNo (Map (Credential 'Staking) (Set Reward)) (Set (Credential 'Staking))
- | TotalRewardEvent EpochNo (Map (Credential 'Staking) (Set Reward))
- | EpochEvent (Event (EraRule "EPOCH" era))
- | MirEvent (Event (EraRule "MIR" era))
- | TotalAdaPotsEvent AdaPots
- updateRewards ∷ (EraGov era, EraCertState era) ⇒ EpochState era → EpochNo → RewardUpdate → Rule (ShelleyNEWEPOCH era) 'Transition (EpochState era)
- newtype Identity a = Identity {
- runIdentity ∷ a
- lift ∷ (MonadTrans t, Monad m) ⇒ m a → t m a
- data PulsingRewUpdate
- type family PredicateFailure a
- type family PredicateFailure a
- epochInfoRange ∷ Monad m ⇒ EpochInfo m → EpochNo → m (SlotNo, SlotNo)
- startStep ∷ (EraGov era, EraCertState era) ⇒ EpochSize → BlocksMade → EpochState era → Coin → ActiveSlotCoeff → NonZero Word64 → PulsingRewUpdate
- pulseStep ∷ PulsingRewUpdate → ShelleyBase (PulsingRewUpdate, RewardEvent)
- completeStep ∷ PulsingRewUpdate → ShelleyBase (PulsingRewUpdate, RewardEvent)
- data ShelleyRUPD era
- data RupdEvent = RupdEvent !EpochNo !(Map (Credential 'Staking) (Set Reward))
- data RupdEnv era = RupdEnv BlocksMade (EpochState era)
- type family PredicateFailure a
- type family PredicateFailure a
- data SnapEnv era = SnapEnv (LedgerState era) (PParams era)
- data ShelleySNAP era
- newtype SnapEvent era = StakeDistEvent (Map (Credential 'Staking) (Coin, KeyHash 'StakePool))
- type family State a
- type family PredicateFailure a
- type family State a
- type family PredicateFailure a
- data ShelleyTICK era
- data ShelleyTICKF era
- data ShelleyTickEvent era
- = TickNewEpochEvent (Event (EraRule "NEWEPOCH" era))
- | TickRupdEvent (Event (EraRule "RUPD" era))
- adoptGenesisDelegs ∷ EraCertState era ⇒ EpochState era → SlotNo → EpochState era
- validatingTickTransition ∷ ∀ tick era. (EraGov era, EraCertState 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 ∷ (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, EraCertState 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)
- type family PredicateFailure a
- type family PredicateFailure a
- data ShelleyMIR era
- data ShelleyMirEvent era
- emptyInstantaneousRewards ∷ InstantaneousRewards
- type family PredicateFailure a
- type family PredicateFailure a
- data ShelleyNEWPP era
- data ShelleyNewppState era = NewppState (PParams era) (ShelleyGovState era)
- data NewppEnv era = NewppEnv {
- neCertState ∷ CertState era
- neUTxOState ∷ UTxOState era
- data ShelleyPoolreapEvent era = RetiredPools {
- refundPools ∷ Map (Credential 'Staking) (Map (KeyHash 'StakePool) (CompactForm Coin))
- unclaimedPools ∷ Map (Credential 'Staking) (Map (KeyHash 'StakePool) (CompactForm Coin))
- epochNo ∷ EpochNo
- type family PredicateFailure a
- type family PredicateFailure a
- data ShelleyPOOLREAP era
- data ShelleyPoolreapState era = PoolreapState {}
- prCertStateL ∷ ∀ era f. Functor f ⇒ (CertState era → f (CertState era)) → ShelleyPoolreapState era → f (ShelleyPoolreapState era)
- prChainAccountStateL ∷ ∀ era f. Functor f ⇒ (ChainAccountState → f ChainAccountState) → ShelleyPoolreapState era → f (ShelleyPoolreapState era)
- prUTxOStateL ∷ ∀ era f. Functor f ⇒ (UTxOState era → f (UTxOState era)) → ShelleyPoolreapState era → f (ShelleyPoolreapState era)
Block
Type of the state which the system transitions between.
Instances
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 ShelleyBBODY era Source #
Instances
data ShelleyBbodyState era Source #
Constructors
| BbodyState !(State (EraRule "LEDGERS" era)) !BlocksMade |
Instances
| Generic (ShelleyBbodyState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Associated Types
Methods from ∷ ShelleyBbodyState era → Rep (ShelleyBbodyState era) x # to ∷ Rep (ShelleyBbodyState era) x → ShelleyBbodyState era # | |||||
| Show (State (EraRule "LEDGERS" era)) ⇒ Show (ShelleyBbodyState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods showsPrec ∷ Int → ShelleyBbodyState era → ShowS # show ∷ ShelleyBbodyState era → String # showList ∷ [ShelleyBbodyState era] → ShowS # | |||||
| Eq (State (EraRule "LEDGERS" era)) ⇒ Eq (ShelleyBbodyState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods (==) ∷ ShelleyBbodyState era → ShelleyBbodyState era → Bool # (/=) ∷ ShelleyBbodyState era → ShelleyBbodyState era → Bool # | |||||
| type Rep (ShelleyBbodyState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody type Rep (ShelleyBbodyState era) = D1 ('MetaData "ShelleyBbodyState" "Cardano.Ledger.Shelley.Rules.Bbody" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "BbodyState" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (State (EraRule "LEDGERS" era))) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 BlocksMade))) | |||||
Constructors
| BbodyEnv | |
Fields
| |
data ShelleyBbodyPredFailure era Source #
Constructors
| WrongBlockBodySizeBBODY (Mismatch 'RelEQ Int) |
|
| InvalidBodyHashBBODY (Mismatch 'RelEQ (Hash HASH EraIndependentBlockBody)) |
|
| LedgersFailure (PredicateFailure (EraRule "LEDGERS" era)) |
Instances
| InjectRuleFailure "BBODY" ShelleyBbodyPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods injectFailure ∷ ShelleyBbodyPredFailure ShelleyEra → EraRuleFailure "BBODY" ShelleyEra Source # | |||||
| (Era era, DecCBOR (PredicateFailure (EraRule "LEDGERS" era))) ⇒ DecCBOR (ShelleyBbodyPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |||||
| (Era era, EncCBOR (PredicateFailure (EraRule "LEDGERS" era))) ⇒ EncCBOR (ShelleyBbodyPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods encCBOR ∷ ShelleyBbodyPredFailure era → Encoding Source # | |||||
| Generic (ShelleyBbodyPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Associated Types
Methods from ∷ ShelleyBbodyPredFailure era → Rep (ShelleyBbodyPredFailure era) x # to ∷ Rep (ShelleyBbodyPredFailure era) x → ShelleyBbodyPredFailure era # | |||||
| (Era era, Show (PredicateFailure (EraRule "LEDGERS" era))) ⇒ Show (ShelleyBbodyPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods showsPrec ∷ Int → ShelleyBbodyPredFailure era → ShowS # show ∷ ShelleyBbodyPredFailure era → String # showList ∷ [ShelleyBbodyPredFailure era] → ShowS # | |||||
| (Era era, Eq (PredicateFailure (EraRule "LEDGERS" era))) ⇒ Eq (ShelleyBbodyPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods (==) ∷ ShelleyBbodyPredFailure era → ShelleyBbodyPredFailure era → Bool # (/=) ∷ ShelleyBbodyPredFailure era → ShelleyBbodyPredFailure era → Bool # | |||||
| (Era era, NoThunks (PredicateFailure (EraRule "LEDGERS" era))) ⇒ NoThunks (ShelleyBbodyPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |||||
| type Rep (ShelleyBbodyPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody type Rep (ShelleyBbodyPredFailure era) = D1 ('MetaData "ShelleyBbodyPredFailure" "Cardano.Ledger.Shelley.Rules.Bbody" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "WrongBlockBodySizeBBODY" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelEQ Int))) :+: (C1 ('MetaCons "InvalidBodyHashBBODY" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelEQ (Hash HASH EraIndependentBlockBody)))) :+: C1 ('MetaCons "LedgersFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PredicateFailure (EraRule "LEDGERS" era)))))) | |||||
newtype ShelleyBbodyEvent era Source #
Constructors
| LedgersEvent (Event (EraRule "LEDGERS" era)) |
Instances
| Generic (ShelleyBbodyEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Associated Types
Methods from ∷ ShelleyBbodyEvent era → Rep (ShelleyBbodyEvent era) x # to ∷ Rep (ShelleyBbodyEvent era) x → ShelleyBbodyEvent era # | |||||
| type Rep (ShelleyBbodyEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody type Rep (ShelleyBbodyEvent era) = D1 ('MetaData "ShelleyBbodyEvent" "Cardano.Ledger.Shelley.Rules.Bbody" "cardano-ledger-shelley-1.18.0.0-inplace" 'True) (C1 ('MetaCons "LedgersEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (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, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
Constructors
| DelegEnv | |
Fields
| |
Instances
| NFData (PParams era) ⇒ NFData (DelegEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |||||
| Generic (DelegEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Associated Types
| |||||
| Show (PParams era) ⇒ Show (DelegEnv era) Source # | |||||
| Eq (PParams era) ⇒ Eq (DelegEnv era) Source # | |||||
| type Rep (DelegEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg type Rep (DelegEnv era) = D1 ('MetaData "DelegEnv" "Cardano.Ledger.Shelley.Rules.Deleg" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "DelegEnv" 'PrefixI 'True) ((S1 ('MetaSel ('Just "slotNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo) :*: S1 ('MetaSel ('Just "deCurEpochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochNo)) :*: (S1 ('MetaSel ('Just "ptr_") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Ptr) :*: (S1 ('MetaSel ('Just "deChainAccountState") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChainAccountState) :*: S1 ('MetaSel ('Just "ppDE") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParams era)))))) | |||||
data ShelleyDELEG era Source #
Instances
| (EraCertState era, EraPParams era, ShelleyEraAccounts era, ShelleyEraTxCert era, AtMostEra "Babbage" era) ⇒ STS (ShelleyDELEG era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Associated Types
Methods initialRules ∷ [InitialRule (ShelleyDELEG era)] Source # transitionRules ∷ [TransitionRule (ShelleyDELEG era)] Source # assertions ∷ [Assertion (ShelleyDELEG era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyDELEG era) → String Source # | |||||||||||||||||||||||||
| (ShelleyEraAccounts era, ShelleyEraTxCert era, EraCertState era, EraPParams era, AtMostEra "Babbage" era, PredicateFailure (EraRule "DELEG" era) ~ ShelleyDelegPredFailure era, Event (EraRule "DELEG" era) ~ ShelleyDelegEvent era) ⇒ Embed (ShelleyDELEG era) (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods wrapFailed ∷ PredicateFailure (ShelleyDELEG era) → PredicateFailure (ShelleyDELPL era) Source # wrapEvent ∷ Event (ShelleyDELEG era) → Event (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyDELEG era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |||||||||||||||||||||||||
| type Environment (ShelleyDELEG era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |||||||||||||||||||||||||
| type Event (ShelleyDELEG era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyDELEG era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |||||||||||||||||||||||||
| type Signal (ShelleyDELEG era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |||||||||||||||||||||||||
| type State (ShelleyDELEG era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |||||||||||||||||||||||||
data ShelleyDelegPredFailure era Source #
Constructors
| StakeKeyAlreadyRegisteredDELEG (Credential 'Staking) | |
| StakeKeyNotRegisteredDELEG (Credential 'Staking) | |
| StakeKeyNonZeroAccountBalanceDELEG Coin | |
| StakeDelegationImpossibleDELEG (Credential 'Staking) | |
| WrongCertificateTypeDELEG | |
| GenesisKeyNotInMappingDELEG (KeyHash 'GenesisRole) | |
| DuplicateGenesisDelegateDELEG (KeyHash 'GenesisDelegate) | |
| InsufficientForInstantaneousRewardsDELEG MIRPot (Mismatch 'RelLTEQ Coin) | |
| MIRCertificateTooLateinEpochDELEG (Mismatch 'RelLT SlotNo) | |
| DuplicateGenesisVRFDELEG (VRFVerKeyHash 'GenDelegVRF) | |
| MIRTransferNotCurrentlyAllowed | |
| MIRNegativesNotCurrentlyAllowed | |
| InsufficientForTransferDELEG MIRPot (Mismatch 'RelLTEQ Coin) | |
| MIRProducesNegativeUpdate | |
| MIRNegativeTransfer MIRPot Coin |
Instances
| InjectRuleFailure "BBODY" ShelleyDelegPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods injectFailure ∷ ShelleyDelegPredFailure ShelleyEra → EraRuleFailure "BBODY" ShelleyEra Source # | |||||
| InjectRuleFailure "DELEG" ShelleyDelegPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Methods injectFailure ∷ ShelleyDelegPredFailure ShelleyEra → EraRuleFailure "DELEG" ShelleyEra Source # | |||||
| InjectRuleFailure "DELEGS" ShelleyDelegPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Methods injectFailure ∷ ShelleyDelegPredFailure ShelleyEra → EraRuleFailure "DELEGS" ShelleyEra Source # | |||||
| InjectRuleFailure "DELPL" ShelleyDelegPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods injectFailure ∷ ShelleyDelegPredFailure ShelleyEra → EraRuleFailure "DELPL" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGER" ShelleyDelegPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods injectFailure ∷ ShelleyDelegPredFailure ShelleyEra → EraRuleFailure "LEDGER" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGERS" ShelleyDelegPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods injectFailure ∷ ShelleyDelegPredFailure ShelleyEra → EraRuleFailure "LEDGERS" ShelleyEra Source # | |||||
| (Era era, Typeable (Script era)) ⇒ DecCBOR (ShelleyDelegPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |||||
| Era era ⇒ EncCBOR (ShelleyDelegPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Methods encCBOR ∷ ShelleyDelegPredFailure era → Encoding Source # | |||||
| NFData (ShelleyDelegPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Methods rnf ∷ ShelleyDelegPredFailure era → () # | |||||
| Generic (ShelleyDelegPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Associated Types
Methods from ∷ ShelleyDelegPredFailure era → Rep (ShelleyDelegPredFailure era) x # to ∷ Rep (ShelleyDelegPredFailure era) x → ShelleyDelegPredFailure era # | |||||
| Show (ShelleyDelegPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Methods showsPrec ∷ Int → ShelleyDelegPredFailure era → ShowS # show ∷ ShelleyDelegPredFailure era → String # showList ∷ [ShelleyDelegPredFailure era] → ShowS # | |||||
| Eq (ShelleyDelegPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Methods (==) ∷ ShelleyDelegPredFailure era → ShelleyDelegPredFailure era → Bool # (/=) ∷ ShelleyDelegPredFailure era → ShelleyDelegPredFailure era → Bool # | |||||
| NoThunks (ShelleyDelegPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |||||
| type Rep (ShelleyDelegPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg type Rep (ShelleyDelegPredFailure era) = D1 ('MetaData "ShelleyDelegPredFailure" "Cardano.Ledger.Shelley.Rules.Deleg" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (((C1 ('MetaCons "StakeKeyAlreadyRegisteredDELEG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Credential 'Staking))) :+: (C1 ('MetaCons "StakeKeyNotRegisteredDELEG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Credential 'Staking))) :+: C1 ('MetaCons "StakeKeyNonZeroAccountBalanceDELEG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin)))) :+: ((C1 ('MetaCons "StakeDelegationImpossibleDELEG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Credential 'Staking))) :+: C1 ('MetaCons "WrongCertificateTypeDELEG" 'PrefixI 'False) (U1 ∷ Type → Type)) :+: (C1 ('MetaCons "GenesisKeyNotInMappingDELEG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'GenesisRole))) :+: C1 ('MetaCons "DuplicateGenesisDelegateDELEG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'GenesisDelegate)))))) :+: (((C1 ('MetaCons "InsufficientForInstantaneousRewardsDELEG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MIRPot) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelLTEQ Coin))) :+: C1 ('MetaCons "MIRCertificateTooLateinEpochDELEG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelLT SlotNo)))) :+: (C1 ('MetaCons "DuplicateGenesisVRFDELEG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VRFVerKeyHash 'GenDelegVRF))) :+: C1 ('MetaCons "MIRTransferNotCurrentlyAllowed" 'PrefixI 'False) (U1 ∷ Type → Type))) :+: ((C1 ('MetaCons "MIRNegativesNotCurrentlyAllowed" 'PrefixI 'False) (U1 ∷ Type → Type) :+: C1 ('MetaCons "InsufficientForTransferDELEG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MIRPot) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelLTEQ Coin)))) :+: (C1 ('MetaCons "MIRProducesNegativeUpdate" 'PrefixI 'False) (U1 ∷ Type → Type) :+: C1 ('MetaCons "MIRNegativeTransfer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MIRPot) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin)))))) | |||||
newtype ShelleyDelegEvent era Source #
Constructors
| DelegNewEpoch EpochNo |
Instances
| NFData (ShelleyDelegEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Methods rnf ∷ ShelleyDelegEvent era → () # | |||||
| Generic (ShelleyDelegEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Associated Types
Methods from ∷ ShelleyDelegEvent era → Rep (ShelleyDelegEvent era) x # to ∷ Rep (ShelleyDelegEvent era) x → ShelleyDelegEvent era # | |||||
| Eq (ShelleyDelegEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Deleg Methods (==) ∷ ShelleyDelegEvent era → ShelleyDelegEvent era → Bool # (/=) ∷ ShelleyDelegEvent era → ShelleyDelegEvent era → Bool # | |||||
| 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.18.0.0-inplace" 'True) (C1 ('MetaCons "DelegNewEpoch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochNo))) | |||||
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
Constructors
| DelegsEnv | |
Fields
| |
data ShelleyDELEGS era Source #
Instances
| (EraTx era, EraCertState era, ShelleyEraTxBody era, Embed (EraRule "DELPL" era) (ShelleyDELEGS era), Environment (EraRule "DELPL" era) ~ DelplEnv era, State (EraRule "DELPL" era) ~ CertState era, Signal (EraRule "DELPL" era) ~ TxCert era, EraRule "DELEGS" era ~ ShelleyDELEGS era) ⇒ STS (ShelleyDELEGS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Associated Types
Methods initialRules ∷ [InitialRule (ShelleyDELEGS era)] Source # transitionRules ∷ [TransitionRule (ShelleyDELEGS era)] Source # assertions ∷ [Assertion (ShelleyDELEGS era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyDELEGS era) → String Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyDELEGS era), PredicateFailure (EraRule "DELEGS" era) ~ ShelleyDelegsPredFailure era, Event (EraRule "DELEGS" era) ~ ShelleyDelegsEvent era) ⇒ Embed (ShelleyDELEGS era) (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods wrapFailed ∷ PredicateFailure (ShelleyDELEGS era) → PredicateFailure (ShelleyLEDGER era) Source # wrapEvent ∷ Event (ShelleyDELEGS era) → Event (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyDELPL era), PredicateFailure (EraRule "DELPL" era) ~ ShelleyDelplPredFailure era, Event (EraRule "DELPL" era) ~ ShelleyDelplEvent era) ⇒ Embed (ShelleyDELPL era) (ShelleyDELEGS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Methods wrapFailed ∷ PredicateFailure (ShelleyDELPL era) → PredicateFailure (ShelleyDELEGS era) Source # wrapEvent ∷ Event (ShelleyDELPL era) → Event (ShelleyDELEGS era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyDELEGS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |||||||||||||||||||||||||
| type Environment (ShelleyDELEGS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |||||||||||||||||||||||||
| type Event (ShelleyDELEGS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyDELEGS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |||||||||||||||||||||||||
| type Signal (ShelleyDELEGS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |||||||||||||||||||||||||
| type State (ShelleyDELEGS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |||||||||||||||||||||||||
data ShelleyDelegsPredFailure era Source #
Constructors
| DelegateeNotRegisteredDELEG (KeyHash 'StakePool) | Target pool which is not registered |
| DelplFailure (PredicateFailure (EraRule "DELPL" era)) | Subtransition Failures |
Instances
| InjectRuleFailure "BBODY" ShelleyDelegsPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods injectFailure ∷ ShelleyDelegsPredFailure ShelleyEra → EraRuleFailure "BBODY" ShelleyEra Source # | |||||
| InjectRuleFailure "DELEGS" ShelleyDelegsPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Methods injectFailure ∷ ShelleyDelegsPredFailure ShelleyEra → EraRuleFailure "DELEGS" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGER" ShelleyDelegsPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods injectFailure ∷ ShelleyDelegsPredFailure ShelleyEra → EraRuleFailure "LEDGER" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGERS" ShelleyDelegsPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods injectFailure ∷ ShelleyDelegsPredFailure ShelleyEra → EraRuleFailure "LEDGERS" ShelleyEra Source # | |||||
| (Era era, DecCBOR (PredicateFailure (EraRule "DELPL" era)), Typeable (Script era)) ⇒ DecCBOR (ShelleyDelegsPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |||||
| (Era era, EncCBOR (PredicateFailure (EraRule "DELPL" era))) ⇒ EncCBOR (ShelleyDelegsPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Methods encCBOR ∷ ShelleyDelegsPredFailure era → Encoding Source # | |||||
| NFData (PredicateFailure (EraRule "DELPL" era)) ⇒ NFData (ShelleyDelegsPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Methods rnf ∷ ShelleyDelegsPredFailure era → () # | |||||
| Generic (ShelleyDelegsPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Associated Types
Methods from ∷ ShelleyDelegsPredFailure era → Rep (ShelleyDelegsPredFailure era) x # to ∷ Rep (ShelleyDelegsPredFailure era) x → ShelleyDelegsPredFailure era # | |||||
| Show (PredicateFailure (EraRule "DELPL" era)) ⇒ Show (ShelleyDelegsPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Methods showsPrec ∷ Int → ShelleyDelegsPredFailure era → ShowS # show ∷ ShelleyDelegsPredFailure era → String # showList ∷ [ShelleyDelegsPredFailure era] → ShowS # | |||||
| Eq (PredicateFailure (EraRule "DELPL" era)) ⇒ Eq (ShelleyDelegsPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Methods (==) ∷ ShelleyDelegsPredFailure era → ShelleyDelegsPredFailure era → Bool # (/=) ∷ ShelleyDelegsPredFailure era → ShelleyDelegsPredFailure era → Bool # | |||||
| NoThunks (PredicateFailure (EraRule "DELPL" era)) ⇒ NoThunks (ShelleyDelegsPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |||||
| type Rep (ShelleyDelegsPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs type Rep (ShelleyDelegsPredFailure era) = D1 ('MetaData "ShelleyDelegsPredFailure" "Cardano.Ledger.Shelley.Rules.Delegs" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "DelegateeNotRegisteredDELEG" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'StakePool))) :+: C1 ('MetaCons "DelplFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PredicateFailure (EraRule "DELPL" era))))) | |||||
newtype ShelleyDelegsEvent era Source #
Constructors
| DelplEvent (Event (EraRule "DELPL" era)) |
Instances
| NFData (Event (EraRule "DELPL" era)) ⇒ NFData (ShelleyDelegsEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Methods rnf ∷ ShelleyDelegsEvent era → () # | |||||
| Generic (ShelleyDelegsEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Associated Types
Methods from ∷ ShelleyDelegsEvent era → Rep (ShelleyDelegsEvent era) x # to ∷ Rep (ShelleyDelegsEvent era) x → ShelleyDelegsEvent era # | |||||
| Eq (Event (EraRule "DELPL" era)) ⇒ Eq (ShelleyDelegsEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Methods (==) ∷ ShelleyDelegsEvent era → ShelleyDelegsEvent era → Bool # (/=) ∷ ShelleyDelegsEvent era → ShelleyDelegsEvent era → Bool # | |||||
| type Rep (ShelleyDelegsEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs type Rep (ShelleyDelegsEvent era) = D1 ('MetaData "ShelleyDelegsEvent" "Cardano.Ledger.Shelley.Rules.Delegs" "cardano-ledger-shelley-1.18.0.0-inplace" 'True) (C1 ('MetaCons "DelplEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "DELPL" era))))) | |||||
validateStakePoolDelegateeRegistered ∷ PState era → KeyHash 'StakePool → Test (KeyHash 'StakePool) Source #
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
Constructors
| DelplEnv | |
Fields
| |
data ShelleyDELPL era Source #
Instances
| (Era era, EraCertState era, Embed (EraRule "DELEG" era) (ShelleyDELPL era), Environment (EraRule "DELEG" era) ~ DelegEnv era, State (EraRule "DELEG" era) ~ CertState era, Embed (EraRule "POOL" era) (ShelleyDELPL era), Environment (EraRule "POOL" era) ~ PoolEnv era, State (EraRule "POOL" era) ~ PState era, Signal (EraRule "DELEG" era) ~ TxCert era, Embed (EraRule "POOL" era) (ShelleyDELPL era), Environment (EraRule "POOL" era) ~ PoolEnv era, Signal (EraRule "POOL" era) ~ PoolCert, TxCert era ~ ShelleyTxCert era) ⇒ STS (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Associated Types
Methods initialRules ∷ [InitialRule (ShelleyDELPL era)] Source # transitionRules ∷ [TransitionRule (ShelleyDELPL era)] Source # assertions ∷ [Assertion (ShelleyDELPL era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyDELPL era) → String Source # | |||||||||||||||||||||||||
| (ShelleyEraAccounts era, ShelleyEraTxCert era, EraCertState era, EraPParams era, AtMostEra "Babbage" era, PredicateFailure (EraRule "DELEG" era) ~ ShelleyDelegPredFailure era, Event (EraRule "DELEG" era) ~ ShelleyDelegEvent era) ⇒ Embed (ShelleyDELEG era) (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods wrapFailed ∷ PredicateFailure (ShelleyDELEG era) → PredicateFailure (ShelleyDELPL era) Source # wrapEvent ∷ Event (ShelleyDELEG era) → Event (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyDELPL era), PredicateFailure (EraRule "DELPL" era) ~ ShelleyDelplPredFailure era, Event (EraRule "DELPL" era) ~ ShelleyDelplEvent era) ⇒ Embed (ShelleyDELPL era) (ShelleyDELEGS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Methods wrapFailed ∷ PredicateFailure (ShelleyDELPL era) → PredicateFailure (ShelleyDELEGS era) Source # wrapEvent ∷ Event (ShelleyDELPL era) → Event (ShelleyDELEGS era) Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyPOOL era), PredicateFailure (EraRule "POOL" era) ~ ShelleyPoolPredFailure era, Event (EraRule "POOL" era) ~ PoolEvent era) ⇒ Embed (ShelleyPOOL era) (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods wrapFailed ∷ PredicateFailure (ShelleyPOOL era) → PredicateFailure (ShelleyDELPL era) Source # wrapEvent ∷ Event (ShelleyPOOL era) → Event (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |||||||||||||||||||||||||
| type Environment (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |||||||||||||||||||||||||
| type Event (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |||||||||||||||||||||||||
| type Signal (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |||||||||||||||||||||||||
| type State (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |||||||||||||||||||||||||
data ShelleyDelplPredFailure era Source #
Constructors
| PoolFailure (PredicateFailure (EraRule "POOL" era)) | |
| DelegFailure (PredicateFailure (EraRule "DELEG" era)) |
Instances
| InjectRuleFailure "BBODY" ShelleyDelplPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods injectFailure ∷ ShelleyDelplPredFailure ShelleyEra → EraRuleFailure "BBODY" ShelleyEra Source # | |||||
| InjectRuleFailure "DELEGS" ShelleyDelplPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Methods injectFailure ∷ ShelleyDelplPredFailure ShelleyEra → EraRuleFailure "DELEGS" ShelleyEra Source # | |||||
| InjectRuleFailure "DELPL" ShelleyDelplPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods injectFailure ∷ ShelleyDelplPredFailure ShelleyEra → EraRuleFailure "DELPL" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGER" ShelleyDelplPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods injectFailure ∷ ShelleyDelplPredFailure ShelleyEra → EraRuleFailure "LEDGER" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGERS" ShelleyDelplPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods injectFailure ∷ ShelleyDelplPredFailure ShelleyEra → EraRuleFailure "LEDGERS" ShelleyEra Source # | |||||
| (Era era, DecCBOR (PredicateFailure (EraRule "POOL" era)), DecCBOR (PredicateFailure (EraRule "DELEG" era)), Typeable (Script era)) ⇒ DecCBOR (ShelleyDelplPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |||||
| (Era era, EncCBOR (PredicateFailure (EraRule "POOL" era)), EncCBOR (PredicateFailure (EraRule "DELEG" era))) ⇒ EncCBOR (ShelleyDelplPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods encCBOR ∷ ShelleyDelplPredFailure era → Encoding Source # | |||||
| (NFData (PredicateFailure (EraRule "DELEG" era)), NFData (PredicateFailure (EraRule "POOL" era))) ⇒ NFData (ShelleyDelplPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods rnf ∷ ShelleyDelplPredFailure era → () # | |||||
| Generic (ShelleyDelplPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Associated Types
Methods from ∷ ShelleyDelplPredFailure era → Rep (ShelleyDelplPredFailure era) x # to ∷ Rep (ShelleyDelplPredFailure era) x → ShelleyDelplPredFailure era # | |||||
| (Show (PredicateFailure (EraRule "DELEG" era)), Show (PredicateFailure (EraRule "POOL" era))) ⇒ Show (ShelleyDelplPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods showsPrec ∷ Int → ShelleyDelplPredFailure era → ShowS # show ∷ ShelleyDelplPredFailure era → String # showList ∷ [ShelleyDelplPredFailure era] → ShowS # | |||||
| (Eq (PredicateFailure (EraRule "DELEG" era)), Eq (PredicateFailure (EraRule "POOL" era))) ⇒ Eq (ShelleyDelplPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods (==) ∷ ShelleyDelplPredFailure era → ShelleyDelplPredFailure era → Bool # (/=) ∷ ShelleyDelplPredFailure era → ShelleyDelplPredFailure era → Bool # | |||||
| (NoThunks (PredicateFailure (EraRule "DELEG" era)), NoThunks (PredicateFailure (EraRule "POOL" era))) ⇒ NoThunks (ShelleyDelplPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |||||
| type Rep (ShelleyDelplPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl type Rep (ShelleyDelplPredFailure era) = D1 ('MetaData "ShelleyDelplPredFailure" "Cardano.Ledger.Shelley.Rules.Delpl" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "PoolFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PredicateFailure (EraRule "POOL" era)))) :+: C1 ('MetaCons "DelegFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PredicateFailure (EraRule "DELEG" era))))) | |||||
data ShelleyDelplEvent era Source #
Instances
| (NFData (Event (EraRule "DELEG" era)), NFData (Event (EraRule "POOL" era))) ⇒ NFData (ShelleyDelplEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods rnf ∷ ShelleyDelplEvent era → () # | |||||
| Generic (ShelleyDelplEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Associated Types
Methods from ∷ ShelleyDelplEvent era → Rep (ShelleyDelplEvent era) x # to ∷ Rep (ShelleyDelplEvent era) x → ShelleyDelplEvent era # | |||||
| (Eq (Event (EraRule "DELEG" era)), Eq (Event (EraRule "POOL" era))) ⇒ Eq (ShelleyDelplEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods (==) ∷ ShelleyDelplEvent era → ShelleyDelplEvent era → Bool # (/=) ∷ ShelleyDelplEvent era → ShelleyDelplEvent era → Bool # | |||||
| type Rep (ShelleyDelplEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl type Rep (ShelleyDelplEvent era) = D1 ('MetaData "ShelleyDelplEvent" "Cardano.Ledger.Shelley.Rules.Delpl" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "PoolEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "POOL" era)))) :+: C1 ('MetaCons "DelegEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "DELEG" era))))) | |||||
Event type.
Instances
| type Event (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type Event (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type Event (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type Event (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type Event (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type Event (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type Event (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type Event (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type Event (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type Event (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type Event (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type Event (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type Event (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type Event (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type Event (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type Event (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type Event (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type Event (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type Event (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type Event (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type Event (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
Event type.
Instances
| type Event (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type Event (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type Event (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type Event (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type Event (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type Event (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type Event (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type Event (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type Event (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type Event (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type Event (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type Event (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type Event (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type Event (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type Event (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type Event (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type Event (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type Event (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type Event (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type Event (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type Event (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
Constructors
| LedgerEnv | |
Fields | |
Instances
| EraPParams era ⇒ EncCBOR (LedgerEnv era) Source # | |||||
| NFData (PParams era) ⇒ NFData (LedgerEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |||||
| Generic (LedgerEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Associated Types
| |||||
| Show (PParams era) ⇒ Show (LedgerEnv era) Source # | |||||
| Eq (PParams era) ⇒ Eq (LedgerEnv era) Source # | |||||
| type Rep (LedgerEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger type Rep (LedgerEnv era) = D1 ('MetaData "LedgerEnv" "Cardano.Ledger.Shelley.Rules.Ledger" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "LedgerEnv" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ledgerSlotNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo) :*: S1 ('MetaSel ('Just "ledgerEpochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe EpochNo))) :*: (S1 ('MetaSel ('Just "ledgerIx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxIx) :*: (S1 ('MetaSel ('Just "ledgerPp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParams era)) :*: S1 ('MetaSel ('Just "ledgerAccount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChainAccountState))))) | |||||
data ShelleyLEDGER era Source #
Instances
| (EraTx era, EraGov era, EraCertState era, Embed (EraRule "DELEGS" era) (ShelleyLEDGER era), Embed (EraRule "UTXOW" era) (ShelleyLEDGER era), Environment (EraRule "UTXOW" era) ~ UtxoEnv era, State (EraRule "UTXOW" era) ~ UTxOState era, Signal (EraRule "UTXOW" era) ~ Tx 'TopTx era, Environment (EraRule "DELEGS" era) ~ DelegsEnv era, State (EraRule "DELEGS" era) ~ CertState era, Signal (EraRule "DELEGS" era) ~ Seq (TxCert era), AtMostEra "Babbage" era, EraRule "LEDGER" era ~ ShelleyLEDGER era, EraRuleFailure "LEDGER" era ~ ShelleyLedgerPredFailure era, InjectRuleFailure "LEDGER" ShelleyLedgerPredFailure era) ⇒ STS (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Associated Types
Methods initialRules ∷ [InitialRule (ShelleyLEDGER era)] Source # transitionRules ∷ [TransitionRule (ShelleyLEDGER era)] Source # assertions ∷ [Assertion (ShelleyLEDGER era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyLEDGER era) → String Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyDELEGS era), PredicateFailure (EraRule "DELEGS" era) ~ ShelleyDelegsPredFailure era, Event (EraRule "DELEGS" era) ~ ShelleyDelegsEvent era) ⇒ Embed (ShelleyDELEGS era) (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods wrapFailed ∷ PredicateFailure (ShelleyDELEGS era) → PredicateFailure (ShelleyLEDGER era) Source # wrapEvent ∷ Event (ShelleyDELEGS era) → Event (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyLEDGER era), PredicateFailure (EraRule "LEDGER" era) ~ ShelleyLedgerPredFailure era, Event (EraRule "LEDGER" era) ~ ShelleyLedgerEvent era) ⇒ Embed (ShelleyLEDGER era) (ShelleyLEDGERS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods wrapFailed ∷ PredicateFailure (ShelleyLEDGER era) → PredicateFailure (ShelleyLEDGERS era) Source # wrapEvent ∷ Event (ShelleyLEDGER era) → Event (ShelleyLEDGERS era) Source # | |||||||||||||||||||||||||
| (STS (ShelleyUTXOW era), PredicateFailure (EraRule "UTXOW" era) ~ ShelleyUtxowPredFailure era, Event (EraRule "UTXOW" era) ~ Event (ShelleyUTXOW era)) ⇒ Embed (ShelleyUTXOW era) (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods wrapFailed ∷ PredicateFailure (ShelleyUTXOW era) → PredicateFailure (ShelleyLEDGER era) Source # wrapEvent ∷ Event (ShelleyUTXOW era) → Event (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |||||||||||||||||||||||||
| type Environment (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |||||||||||||||||||||||||
| type Event (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |||||||||||||||||||||||||
| type Signal (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |||||||||||||||||||||||||
| type State (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |||||||||||||||||||||||||
data ShelleyLedgerPredFailure era Source #
Constructors
| UtxowFailure (PredicateFailure (EraRule "UTXOW" era)) | |
| DelegsFailure (PredicateFailure (EraRule "DELEGS" era)) | |
| ShelleyWithdrawalsMissingAccounts Withdrawals | |
| ShelleyIncompleteWithdrawals Withdrawals |
Instances
| InjectRuleFailure "BBODY" ShelleyLedgerPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods injectFailure ∷ ShelleyLedgerPredFailure ShelleyEra → EraRuleFailure "BBODY" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGER" ShelleyLedgerPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods injectFailure ∷ ShelleyLedgerPredFailure ShelleyEra → EraRuleFailure "LEDGER" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGERS" ShelleyLedgerPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods injectFailure ∷ ShelleyLedgerPredFailure ShelleyEra → EraRuleFailure "LEDGERS" ShelleyEra Source # | |||||
| (DecCBOR (PredicateFailure (EraRule "DELEGS" era)), DecCBOR (PredicateFailure (EraRule "UTXOW" era)), Era era) ⇒ DecCBOR (ShelleyLedgerPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |||||
| (EncCBOR (PredicateFailure (EraRule "DELEGS" era)), EncCBOR (PredicateFailure (EraRule "UTXOW" era)), Era era) ⇒ EncCBOR (ShelleyLedgerPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods encCBOR ∷ ShelleyLedgerPredFailure era → Encoding Source # | |||||
| (NFData (PredicateFailure (EraRule "DELEGS" era)), NFData (PredicateFailure (EraRule "UTXOW" era)), Era era) ⇒ NFData (ShelleyLedgerPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods rnf ∷ ShelleyLedgerPredFailure era → () # | |||||
| Generic (ShelleyLedgerPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Associated Types
Methods from ∷ ShelleyLedgerPredFailure era → Rep (ShelleyLedgerPredFailure era) x # to ∷ Rep (ShelleyLedgerPredFailure era) x → ShelleyLedgerPredFailure era # | |||||
| (Show (PredicateFailure (EraRule "DELEGS" era)), Show (PredicateFailure (EraRule "UTXOW" era)), Era era) ⇒ Show (ShelleyLedgerPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods showsPrec ∷ Int → ShelleyLedgerPredFailure era → ShowS # show ∷ ShelleyLedgerPredFailure era → String # showList ∷ [ShelleyLedgerPredFailure era] → ShowS # | |||||
| (Eq (PredicateFailure (EraRule "DELEGS" era)), Eq (PredicateFailure (EraRule "UTXOW" era)), Era era) ⇒ Eq (ShelleyLedgerPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods (==) ∷ ShelleyLedgerPredFailure era → ShelleyLedgerPredFailure era → Bool # (/=) ∷ ShelleyLedgerPredFailure era → ShelleyLedgerPredFailure era → Bool # | |||||
| (NoThunks (PredicateFailure (EraRule "DELEGS" era)), NoThunks (PredicateFailure (EraRule "UTXOW" era)), Era era) ⇒ NoThunks (ShelleyLedgerPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |||||
| type Rep (ShelleyLedgerPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger type Rep (ShelleyLedgerPredFailure era) = D1 ('MetaData "ShelleyLedgerPredFailure" "Cardano.Ledger.Shelley.Rules.Ledger" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) ((C1 ('MetaCons "UtxowFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PredicateFailure (EraRule "UTXOW" era)))) :+: C1 ('MetaCons "DelegsFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PredicateFailure (EraRule "DELEGS" era))))) :+: (C1 ('MetaCons "ShelleyWithdrawalsMissingAccounts" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Withdrawals)) :+: C1 ('MetaCons "ShelleyIncompleteWithdrawals" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Withdrawals)))) | |||||
ledgerSlotNoL ∷ ∀ era f. Functor f ⇒ (SlotNo → f SlotNo) → LedgerEnv era → f (LedgerEnv era) Source #
ledgerEpochNoL ∷ ∀ era f. Functor f ⇒ (Maybe EpochNo → f (Maybe EpochNo)) → LedgerEnv era → f (LedgerEnv era) Source #
ledgerPpL ∷ ∀ era f. Functor f ⇒ (PParams era → f (PParams era)) → LedgerEnv era → f (LedgerEnv era) Source #
ledgerAccountL ∷ ∀ era f. Functor f ⇒ (ChainAccountState → f ChainAccountState) → LedgerEnv era → f (LedgerEnv era) Source #
data ShelleyLedgerEvent era Source #
Constructors
| UtxowEvent (Event (EraRule "UTXOW" era)) | |
| DelegsEvent (Event (EraRule "DELEGS" era)) |
Instances
| (NFData (Event (EraRule "UTXOW" era)), NFData (Event (EraRule "DELEGS" era))) ⇒ NFData (ShelleyLedgerEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods rnf ∷ ShelleyLedgerEvent era → () # | |||||
| Generic (ShelleyLedgerEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Associated Types
Methods from ∷ ShelleyLedgerEvent era → Rep (ShelleyLedgerEvent era) x # to ∷ Rep (ShelleyLedgerEvent era) x → ShelleyLedgerEvent era # | |||||
| (Eq (Event (EraRule "UTXOW" era)), Eq (Event (EraRule "DELEGS" era))) ⇒ Eq (ShelleyLedgerEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods (==) ∷ ShelleyLedgerEvent era → ShelleyLedgerEvent era → Bool # (/=) ∷ ShelleyLedgerEvent era → ShelleyLedgerEvent era → Bool # | |||||
| type Rep (ShelleyLedgerEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger type Rep (ShelleyLedgerEvent era) = D1 ('MetaData "ShelleyLedgerEvent" "Cardano.Ledger.Shelley.Rules.Ledger" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "UtxowEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "UTXOW" era)))) :+: C1 ('MetaCons "DelegsEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "DELEGS" era))))) | |||||
renderDepositEqualsObligationViolation ∷ (EraTx era, EraGov era, EraCertState era, Environment t ~ LedgerEnv era, Signal t ~ Tx 'TopTx era, State t ~ LedgerState era) ⇒ AssertionViolation t → String Source #
shelleyLedgerAssertions ∷ (EraGov era, EraCertState era, State (rule era) ~ LedgerState era) ⇒ [Assertion (rule era)] Source #
testIncompleteAndMissingWithdrawals ∷ ∀ era sts (ctx ∷ RuleType). (EraAccounts era, STS sts, BaseM sts ~ ShelleyBase, InjectRuleFailure "LEDGER" ShelleyLedgerPredFailure era, sts ~ EraRule "LEDGER" era) ⇒ Accounts era → Withdrawals → Rule sts ctx () Source #
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
data ShelleyLEDGERS era Source #
Instances
| (Era era, Embed (EraRule "LEDGER" era) (ShelleyLEDGERS era), Environment (EraRule "LEDGER" era) ~ LedgerEnv era, State (EraRule "LEDGER" era) ~ LedgerState era, Signal (EraRule "LEDGER" era) ~ Tx 'TopTx era, Default (LedgerState era)) ⇒ STS (ShelleyLEDGERS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Associated Types
Methods initialRules ∷ [InitialRule (ShelleyLEDGERS era)] Source # transitionRules ∷ [TransitionRule (ShelleyLEDGERS era)] Source # assertions ∷ [Assertion (ShelleyLEDGERS era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyLEDGERS era) → String Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyLEDGER era), PredicateFailure (EraRule "LEDGER" era) ~ ShelleyLedgerPredFailure era, Event (EraRule "LEDGER" era) ~ ShelleyLedgerEvent era) ⇒ Embed (ShelleyLEDGER era) (ShelleyLEDGERS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods wrapFailed ∷ PredicateFailure (ShelleyLEDGER era) → PredicateFailure (ShelleyLEDGERS era) Source # wrapEvent ∷ Event (ShelleyLEDGER era) → Event (ShelleyLEDGERS era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyLEDGERS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |||||||||||||||||||||||||
| type Environment (ShelleyLEDGERS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |||||||||||||||||||||||||
| type Event (ShelleyLEDGERS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyLEDGERS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |||||||||||||||||||||||||
| type Signal (ShelleyLEDGERS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |||||||||||||||||||||||||
| type State (ShelleyLEDGERS era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |||||||||||||||||||||||||
data ShelleyLedgersEnv era Source #
Constructors
| LedgersEnv | |
Fields | |
Instances
| EraPParams era ⇒ EncCBOR (ShelleyLedgersEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods encCBOR ∷ ShelleyLedgersEnv era → Encoding Source # | |||||
| NFData (PParamsHKD Identity era) ⇒ NFData (ShelleyLedgersEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods rnf ∷ ShelleyLedgersEnv era → () # | |||||
| Generic (ShelleyLedgersEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Associated Types
Methods from ∷ ShelleyLedgersEnv era → Rep (ShelleyLedgersEnv era) x # to ∷ Rep (ShelleyLedgersEnv era) x → ShelleyLedgersEnv era # | |||||
| Show (PParamsHKD Identity era) ⇒ Show (ShelleyLedgersEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods showsPrec ∷ Int → ShelleyLedgersEnv era → ShowS # show ∷ ShelleyLedgersEnv era → String # showList ∷ [ShelleyLedgersEnv era] → ShowS # | |||||
| Eq (PParamsHKD Identity era) ⇒ Eq (ShelleyLedgersEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods (==) ∷ ShelleyLedgersEnv era → ShelleyLedgersEnv era → Bool # (/=) ∷ ShelleyLedgersEnv era → ShelleyLedgersEnv era → Bool # | |||||
| type Rep (ShelleyLedgersEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers type Rep (ShelleyLedgersEnv era) = D1 ('MetaData "ShelleyLedgersEnv" "Cardano.Ledger.Shelley.Rules.Ledgers" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "LedgersEnv" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ledgersSlotNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SlotNo) :*: S1 ('MetaSel ('Just "ledgersEpochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochNo)) :*: (S1 ('MetaSel ('Just "ledgersPp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParams era)) :*: S1 ('MetaSel ('Just "ledgersAccount") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ChainAccountState)))) | |||||
newtype ShelleyLedgersPredFailure era Source #
Constructors
| LedgerFailure (PredicateFailure (EraRule "LEDGER" era)) |
Instances
| InjectRuleFailure "BBODY" ShelleyLedgersPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods injectFailure ∷ ShelleyLedgersPredFailure ShelleyEra → EraRuleFailure "BBODY" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGERS" ShelleyLedgersPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods injectFailure ∷ ShelleyLedgersPredFailure ShelleyEra → EraRuleFailure "LEDGERS" ShelleyEra Source # | |||||
| (Era era, DecCBOR (PredicateFailure (EraRule "LEDGER" era))) ⇒ DecCBOR (ShelleyLedgersPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |||||
| (Era era, EncCBOR (PredicateFailure (EraRule "LEDGER" era))) ⇒ EncCBOR (ShelleyLedgersPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods encCBOR ∷ ShelleyLedgersPredFailure era → Encoding Source # | |||||
| NFData (PredicateFailure (EraRule "LEDGER" era)) ⇒ NFData (ShelleyLedgersPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods rnf ∷ ShelleyLedgersPredFailure era → () # | |||||
| Generic (ShelleyLedgersPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Associated Types
Methods from ∷ ShelleyLedgersPredFailure era → Rep (ShelleyLedgersPredFailure era) x # to ∷ Rep (ShelleyLedgersPredFailure era) x → ShelleyLedgersPredFailure era # | |||||
| (Era era, Show (PredicateFailure (EraRule "LEDGER" era))) ⇒ Show (ShelleyLedgersPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods showsPrec ∷ Int → ShelleyLedgersPredFailure era → ShowS # show ∷ ShelleyLedgersPredFailure era → String # showList ∷ [ShelleyLedgersPredFailure era] → ShowS # | |||||
| (Era era, Eq (PredicateFailure (EraRule "LEDGER" era))) ⇒ Eq (ShelleyLedgersPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods (==) ∷ ShelleyLedgersPredFailure era → ShelleyLedgersPredFailure era → Bool # (/=) ∷ ShelleyLedgersPredFailure era → ShelleyLedgersPredFailure era → Bool # | |||||
| (Era era, NoThunks (PredicateFailure (EraRule "LEDGER" era))) ⇒ NoThunks (ShelleyLedgersPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |||||
| type Rep (ShelleyLedgersPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers type Rep (ShelleyLedgersPredFailure era) = D1 ('MetaData "ShelleyLedgersPredFailure" "Cardano.Ledger.Shelley.Rules.Ledgers" "cardano-ledger-shelley-1.18.0.0-inplace" 'True) (C1 ('MetaCons "LedgerFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PredicateFailure (EraRule "LEDGER" era))))) | |||||
newtype ShelleyLedgersEvent era Source #
Constructors
| LedgerEvent (Event (EraRule "LEDGER" era)) |
Instances
| Generic (ShelleyLedgersEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Associated Types
Methods from ∷ ShelleyLedgersEvent era → Rep (ShelleyLedgersEvent era) x # to ∷ Rep (ShelleyLedgersEvent era) x → ShelleyLedgersEvent era # | |||||
| type Rep (ShelleyLedgersEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers type Rep (ShelleyLedgersEvent era) = D1 ('MetaData "ShelleyLedgersEvent" "Cardano.Ledger.Shelley.Rules.Ledgers" "cardano-ledger-shelley-1.18.0.0-inplace" 'True) (C1 ('MetaCons "LedgerEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (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, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
Instances
| EraPParams era ⇒ EncCBOR (PoolEnv era) Source # | |||||
| NFData (PParams era) ⇒ NFData (PoolEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool | |||||
| Generic (PoolEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool Associated Types
| |||||
| Show (PParams era) ⇒ Show (PoolEnv era) Source # | |||||
| 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.18.0.0-inplace" 'False) (C1 ('MetaCons "PoolEnv" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochNo) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParams era)))) | |||||
data ShelleyPOOL era Source #
Instances
| EraPParams era ⇒ STS (ShelleyPOOL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Pool Associated Types
Methods initialRules ∷ [InitialRule (ShelleyPOOL era)] Source # transitionRules ∷ [TransitionRule (ShelleyPOOL era)] Source # assertions ∷ [Assertion (ShelleyPOOL era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyPOOL era) → String Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyPOOL era), PredicateFailure (EraRule "POOL" era) ~ ShelleyPoolPredFailure era, Event (EraRule "POOL" era) ~ PoolEvent era) ⇒ Embed (ShelleyPOOL era) (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods wrapFailed ∷ PredicateFailure (ShelleyPOOL era) → PredicateFailure (ShelleyDELPL era) Source # wrapEvent ∷ Event (ShelleyPOOL era) → Event (ShelleyDELPL era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyPOOL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Pool | |||||||||||||||||||||||||
| type Environment (ShelleyPOOL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Pool | |||||||||||||||||||||||||
| type Event (ShelleyPOOL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Pool | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyPOOL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Pool | |||||||||||||||||||||||||
| type Signal (ShelleyPOOL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Pool | |||||||||||||||||||||||||
| type State (ShelleyPOOL era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Pool | |||||||||||||||||||||||||
data ShelleyPoolPredFailure era Source #
Constructors
| StakePoolNotRegisteredOnKeyPOOL | |
| StakePoolRetirementWrongEpochPOOL (Mismatch 'RelGT EpochNo) (Mismatch 'RelLTEQ EpochNo) | |
| StakePoolCostTooLowPOOL (Mismatch 'RelGTEQ Coin) | |
| WrongNetworkPOOL | |
| PoolMedataHashTooBig | |
| VRFKeyHashAlreadyRegistered | |
Fields
| |
Instances
| InjectRuleFailure "BBODY" ShelleyPoolPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods injectFailure ∷ ShelleyPoolPredFailure ShelleyEra → EraRuleFailure "BBODY" ShelleyEra Source # | |||||
| InjectRuleFailure "DELEGS" ShelleyPoolPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delegs Methods injectFailure ∷ ShelleyPoolPredFailure ShelleyEra → EraRuleFailure "DELEGS" ShelleyEra Source # | |||||
| InjectRuleFailure "DELPL" ShelleyPoolPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Delpl Methods injectFailure ∷ ShelleyPoolPredFailure ShelleyEra → EraRuleFailure "DELPL" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGER" ShelleyPoolPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods injectFailure ∷ ShelleyPoolPredFailure ShelleyEra → EraRuleFailure "LEDGER" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGERS" ShelleyPoolPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods injectFailure ∷ ShelleyPoolPredFailure ShelleyEra → EraRuleFailure "LEDGERS" ShelleyEra Source # | |||||
| InjectRuleFailure "POOL" ShelleyPoolPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool Methods injectFailure ∷ ShelleyPoolPredFailure ShelleyEra → EraRuleFailure "POOL" ShelleyEra Source # | |||||
| Era era ⇒ DecCBOR (ShelleyPoolPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool | |||||
| Era era ⇒ EncCBOR (ShelleyPoolPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool Methods encCBOR ∷ ShelleyPoolPredFailure era → Encoding Source # | |||||
| NFData (ShelleyPoolPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool Methods rnf ∷ ShelleyPoolPredFailure era → () # | |||||
| Generic (ShelleyPoolPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool Associated Types
Methods from ∷ ShelleyPoolPredFailure era → Rep (ShelleyPoolPredFailure era) x # to ∷ Rep (ShelleyPoolPredFailure era) x → ShelleyPoolPredFailure era # | |||||
| Show (ShelleyPoolPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool Methods showsPrec ∷ Int → ShelleyPoolPredFailure era → ShowS # show ∷ ShelleyPoolPredFailure era → String # showList ∷ [ShelleyPoolPredFailure era] → ShowS # | |||||
| Eq (ShelleyPoolPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool Methods (==) ∷ ShelleyPoolPredFailure era → ShelleyPoolPredFailure era → Bool # (/=) ∷ ShelleyPoolPredFailure era → ShelleyPoolPredFailure era → Bool # | |||||
| NoThunks (ShelleyPoolPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool | |||||
| type Rep (ShelleyPoolPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool type Rep (ShelleyPoolPredFailure era) = D1 ('MetaData "ShelleyPoolPredFailure" "Cardano.Ledger.Shelley.Rules.Pool" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) ((C1 ('MetaCons "StakePoolNotRegisteredOnKeyPOOL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'StakePool))) :+: (C1 ('MetaCons "StakePoolRetirementWrongEpochPOOL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelGT EpochNo)) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelLTEQ EpochNo))) :+: C1 ('MetaCons "StakePoolCostTooLowPOOL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelGTEQ Coin))))) :+: (C1 ('MetaCons "WrongNetworkPOOL" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelEQ Network)) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'StakePool))) :+: (C1 ('MetaCons "PoolMedataHashTooBig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'StakePool)) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :+: C1 ('MetaCons "VRFKeyHashAlreadyRegistered" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'StakePool)) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VRFVerKeyHash 'StakePoolVRF)))))) | |||||
Constructors
| RegisterPool (KeyHash 'StakePool) | |
| ReregisterPool (KeyHash 'StakePool) |
Instances
| NFData (PoolEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool | |||||
| Generic (PoolEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Pool Associated Types
| |||||
| 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.18.0.0-inplace" 'False) (C1 ('MetaCons "RegisterPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'StakePool))) :+: C1 ('MetaCons "ReregisterPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (KeyHash 'StakePool)))) | |||||
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
data ShelleyGovState era Source #
Constructors
| ShelleyGovState | |
Fields
| |
Instances
| EraPParams era ⇒ ToJSON (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance Methods toJSON ∷ ShelleyGovState era → Value Source # toEncoding ∷ ShelleyGovState era → Encoding Source # toJSONList ∷ [ShelleyGovState era] → Value Source # toEncodingList ∷ [ShelleyGovState era] → Encoding Source # omitField ∷ ShelleyGovState era → Bool Source # | |||||
| (Era era, DecCBOR (PParamsUpdate era), DecCBOR (PParams era)) ⇒ FromCBOR (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance | |||||
| (Era era, EncCBOR (PParamsUpdate era), EncCBOR (PParams era)) ⇒ ToCBOR (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance Methods toCBOR ∷ ShelleyGovState era → Encoding Source # encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (ShelleyGovState era) → Size Source # encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [ShelleyGovState era] → Size Source # | |||||
| (Era era, DecCBOR (PParamsUpdate era), DecCBOR (PParams era)) ⇒ DecCBOR (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance | |||||
| (Era era, DecCBOR (PParamsUpdate era), DecCBOR (PParams era)) ⇒ DecShareCBOR (ShelleyGovState era) Source # | |||||
| (Era era, EncCBOR (PParamsUpdate era), EncCBOR (PParams era)) ⇒ EncCBOR (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance Methods encCBOR ∷ ShelleyGovState era → Encoding Source # | |||||
| EraPParams era ⇒ ToKeyValuePairs (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance Methods toKeyValuePairs ∷ KeyValue e kv ⇒ ShelleyGovState era → [kv] Source # | |||||
| EraPParams era ⇒ Default (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance Methods def ∷ ShelleyGovState era Source # | |||||
| (NFData (PParamsUpdate era), NFData (PParams era)) ⇒ NFData (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance Methods rnf ∷ ShelleyGovState era → () # | |||||
| Generic (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance Associated Types
Methods from ∷ ShelleyGovState era → Rep (ShelleyGovState era) x # to ∷ Rep (ShelleyGovState era) x → ShelleyGovState era # | |||||
| (Show (PParamsUpdate era), Show (PParams era)) ⇒ Show (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance Methods showsPrec ∷ Int → ShelleyGovState era → ShowS # show ∷ ShelleyGovState era → String # showList ∷ [ShelleyGovState era] → ShowS # | |||||
| (Eq (PParamsUpdate era), Eq (PParams era)) ⇒ Eq (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance Methods (==) ∷ ShelleyGovState era → ShelleyGovState era → Bool # (/=) ∷ ShelleyGovState era → ShelleyGovState era → Bool # | |||||
| (NoThunks (PParamsUpdate era), NoThunks (PParams era)) ⇒ NoThunks (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance | |||||
| type Share (ShelleyGovState era) Source # | |||||
| type Rep (ShelleyGovState era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Governance type Rep (ShelleyGovState era) = D1 ('MetaData "ShelleyGovState" "Cardano.Ledger.Shelley.Governance" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "ShelleyGovState" 'PrefixI 'True) ((S1 ('MetaSel ('Just "sgsCurProposals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ProposedPPUpdates era)) :*: S1 ('MetaSel ('Just "sgsFutureProposals") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ProposedPPUpdates era))) :*: (S1 ('MetaSel ('Just "sgsCurPParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PParams era)) :*: (S1 ('MetaSel ('Just "sgsPrevPParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PParams era)) :*: S1 ('MetaSel ('Just "sgsFuturePParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (FuturePParams era)))))) | |||||
data ShelleyPPUP era Source #
Instances
| (EraPParams era, AtMostEra "Babbage" era) ⇒ STS (ShelleyPPUP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Associated Types
Methods initialRules ∷ [InitialRule (ShelleyPPUP era)] Source # transitionRules ∷ [TransitionRule (ShelleyPPUP era)] Source # assertions ∷ [Assertion (ShelleyPPUP era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyPPUP era) → String Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyPPUP era), EraRuleFailure "PPUP" era ~ ShelleyPpupPredFailure era, Event (EraRule "PPUP" era) ~ PpupEvent era) ⇒ Embed (ShelleyPPUP era) (ShelleyUTXO era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Methods wrapFailed ∷ PredicateFailure (ShelleyPPUP era) → PredicateFailure (ShelleyUTXO era) Source # wrapEvent ∷ Event (ShelleyPPUP era) → Event (ShelleyUTXO era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyPPUP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||||||||||||||||||||||
| type Environment (ShelleyPPUP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||||||||||||||||||||||
| type Event (ShelleyPPUP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyPPUP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||||||||||||||||||||||
| type Signal (ShelleyPPUP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||||||||||||||||||||||
| type State (ShelleyPPUP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||||||||||||||||||||||
data ShelleyPpupPredFailure era Source #
Constructors
| NonGenesisUpdatePPUP (Mismatch 'RelSubset (Set (KeyHash 'GenesisRole))) | 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
| InjectRuleFailure "BBODY" ShelleyPpupPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods injectFailure ∷ ShelleyPpupPredFailure ShelleyEra → EraRuleFailure "BBODY" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGER" ShelleyPpupPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods injectFailure ∷ ShelleyPpupPredFailure ShelleyEra → EraRuleFailure "LEDGER" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGERS" ShelleyPpupPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods injectFailure ∷ ShelleyPpupPredFailure ShelleyEra → EraRuleFailure "LEDGERS" ShelleyEra Source # | |||||
| InjectRuleFailure "PPUP" ShelleyPpupPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Methods injectFailure ∷ ShelleyPpupPredFailure ShelleyEra → EraRuleFailure "PPUP" ShelleyEra Source # | |||||
| InjectRuleFailure "UTXO" ShelleyPpupPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Methods injectFailure ∷ ShelleyPpupPredFailure ShelleyEra → EraRuleFailure "UTXO" ShelleyEra Source # | |||||
| InjectRuleFailure "UTXOW" ShelleyPpupPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Methods injectFailure ∷ ShelleyPpupPredFailure ShelleyEra → EraRuleFailure "UTXOW" ShelleyEra Source # | |||||
| Era era ⇒ DecCBOR (ShelleyPpupPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||
| Era era ⇒ EncCBOR (ShelleyPpupPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Methods encCBOR ∷ ShelleyPpupPredFailure era → Encoding Source # | |||||
| NFData (ShelleyPpupPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Methods rnf ∷ ShelleyPpupPredFailure era → () # | |||||
| Generic (ShelleyPpupPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Associated Types
Methods from ∷ ShelleyPpupPredFailure era → Rep (ShelleyPpupPredFailure era) x # to ∷ Rep (ShelleyPpupPredFailure era) x → ShelleyPpupPredFailure era # | |||||
| Show (ShelleyPpupPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Methods showsPrec ∷ Int → ShelleyPpupPredFailure era → ShowS # show ∷ ShelleyPpupPredFailure era → String # showList ∷ [ShelleyPpupPredFailure era] → ShowS # | |||||
| Eq (ShelleyPpupPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Methods (==) ∷ ShelleyPpupPredFailure era → ShelleyPpupPredFailure era → Bool # (/=) ∷ ShelleyPpupPredFailure era → ShelleyPpupPredFailure era → Bool # | |||||
| NoThunks (ShelleyPpupPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||
| type Rep (ShelleyPpupPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup type Rep (ShelleyPpupPredFailure era) = D1 ('MetaData "ShelleyPpupPredFailure" "Cardano.Ledger.Shelley.Rules.Ppup" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "NonGenesisUpdatePPUP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelSubset (Set (KeyHash 'GenesisRole))))) :+: (C1 ('MetaCons "PPUpdateWrongEpoch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochNo) :*: (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochNo) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 VotingPeriod))) :+: C1 ('MetaCons "PVCannotFollowPPUP" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ProtVer)))) | |||||
Arguments
| ∷ 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.
newtype PpupEvent era Source #
Constructors
| PpupNewEpoch EpochNo |
Instances
| NFData (PpupEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||
| Generic (PpupEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Associated Types
| |||||
| Eq (PpupEvent era) Source # | |||||
| type Rep (PpupEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||
data VotingPeriod Source #
Constructors
| VoteForThisEpoch | |
| VoteForNextEpoch |
Instances
| DecCBOR VotingPeriod Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||
| EncCBOR VotingPeriod Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Methods | |||||
| NFData VotingPeriod Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Methods rnf ∷ VotingPeriod → () # | |||||
| Generic VotingPeriod Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Associated Types
| |||||
| Show VotingPeriod Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup Methods showsPrec ∷ Int → VotingPeriod → ShowS # show ∷ VotingPeriod → String # showList ∷ [VotingPeriod] → ShowS # | |||||
| Eq VotingPeriod Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||
| NoThunks VotingPeriod Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||
| type Rep VotingPeriod Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |||||
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
data ShelleyUTXO era Source #
Instances
| (EraTx era, EraUTxO era, EraStake era, ShelleyEraTxBody era, EraGov era, GovState era ~ ShelleyGovState era, ExactEra ShelleyEra era, Embed (EraRule "PPUP" era) (ShelleyUTXO era), Environment (EraRule "PPUP" era) ~ PpupEnv era, Signal (EraRule "PPUP" era) ~ StrictMaybe (Update era), State (EraRule "PPUP" era) ~ ShelleyGovState era, Eq (EraRuleFailure "PPUP" era), Show (EraRuleFailure "PPUP" era), EraRule "UTXO" era ~ ShelleyUTXO era, InjectRuleFailure "UTXO" ShelleyUtxoPredFailure era, EraCertState era, SafeToHash (TxWits era)) ⇒ STS (ShelleyUTXO era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Associated Types
Methods initialRules ∷ [InitialRule (ShelleyUTXO era)] Source # transitionRules ∷ [TransitionRule (ShelleyUTXO era)] Source # assertions ∷ [Assertion (ShelleyUTXO era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyUTXO era) → String Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyPPUP era), EraRuleFailure "PPUP" era ~ ShelleyPpupPredFailure era, Event (EraRule "PPUP" era) ~ PpupEvent era) ⇒ Embed (ShelleyPPUP era) (ShelleyUTXO era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Methods wrapFailed ∷ PredicateFailure (ShelleyPPUP era) → PredicateFailure (ShelleyUTXO era) Source # wrapEvent ∷ Event (ShelleyPPUP era) → Event (ShelleyUTXO era) Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyUTXO era), PredicateFailure (EraRule "UTXO" era) ~ ShelleyUtxoPredFailure era, Event (EraRule "UTXO" era) ~ UtxoEvent era) ⇒ Embed (ShelleyUTXO era) (ShelleyUTXOW era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Methods wrapFailed ∷ PredicateFailure (ShelleyUTXO era) → PredicateFailure (ShelleyUTXOW era) Source # wrapEvent ∷ Event (ShelleyUTXO era) → Event (ShelleyUTXOW era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyUTXO era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |||||||||||||||||||||||||
| type Environment (ShelleyUTXO era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |||||||||||||||||||||||||
| type Event (ShelleyUTXO era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyUTXO era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |||||||||||||||||||||||||
| type Signal (ShelleyUTXO era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |||||||||||||||||||||||||
| type State (ShelleyUTXO era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |||||||||||||||||||||||||
Instances
| (EraPParams era, EraCertState era, Typeable (CertState era)) ⇒ DecCBOR (UtxoEnv era) Source # | |||||
| (EraPParams era, EraCertState era) ⇒ EncCBOR (UtxoEnv era) Source # | |||||
| (Era era, NFData (PParams era), NFData (CertState era)) ⇒ NFData (UtxoEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |||||
| Generic (UtxoEnv era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Associated Types
| |||||
| (Show (PParams era), Show (CertState era)) ⇒ Show (UtxoEnv era) Source # | |||||
| (Eq (PParams era), Eq (CertState 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.18.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 #
Constructors
| BadInputsUTxO (Set TxIn) | |
| ExpiredUTxO (Mismatch 'RelLTEQ SlotNo) | |
| MaxTxSizeUTxO (Mismatch 'RelLTEQ Word32) | |
| InputSetEmptyUTxO | |
| FeeTooSmallUTxO (Mismatch 'RelGTEQ Coin) | |
| ValueNotConservedUTxO (Mismatch 'RelEQ (Value era)) | |
| WrongNetwork Network (Set Addr) | |
| WrongNetworkWithdrawal Network (Set RewardAccount) | |
| OutputTooSmallUTxO [TxOut era] | |
| UpdateFailure (EraRuleFailure "PPUP" era) | |
| OutputBootAddrAttrsTooBig [TxOut era] |
Instances
| InjectRuleFailure "BBODY" ShelleyUtxoPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods injectFailure ∷ ShelleyUtxoPredFailure ShelleyEra → EraRuleFailure "BBODY" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGER" ShelleyUtxoPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods injectFailure ∷ ShelleyUtxoPredFailure ShelleyEra → EraRuleFailure "LEDGER" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGERS" ShelleyUtxoPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods injectFailure ∷ ShelleyUtxoPredFailure ShelleyEra → EraRuleFailure "LEDGERS" ShelleyEra Source # | |||||
| InjectRuleFailure "UTXO" ShelleyUtxoPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Methods injectFailure ∷ ShelleyUtxoPredFailure ShelleyEra → EraRuleFailure "UTXO" ShelleyEra Source # | |||||
| InjectRuleFailure "UTXOW" ShelleyUtxoPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Methods injectFailure ∷ ShelleyUtxoPredFailure ShelleyEra → EraRuleFailure "UTXOW" ShelleyEra Source # | |||||
| (EraTxOut era, DecCBOR (EraRuleFailure "PPUP" era)) ⇒ DecCBOR (ShelleyUtxoPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |||||
| (Era era, EncCBOR (Value era), EncCBOR (TxOut era), EncCBOR (EraRuleFailure "PPUP" era)) ⇒ EncCBOR (ShelleyUtxoPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Methods encCBOR ∷ ShelleyUtxoPredFailure era → Encoding Source # | |||||
| (Era era, NFData (Value era), NFData (TxOut era), NFData (EraRuleFailure "PPUP" era)) ⇒ NFData (ShelleyUtxoPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Methods rnf ∷ ShelleyUtxoPredFailure era → () # | |||||
| Generic (ShelleyUtxoPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Associated Types
Methods from ∷ ShelleyUtxoPredFailure era → Rep (ShelleyUtxoPredFailure era) x # to ∷ Rep (ShelleyUtxoPredFailure era) x → ShelleyUtxoPredFailure era # | |||||
| (Show (Value era), Show (TxOut era), Show (EraRuleFailure "PPUP" era)) ⇒ Show (ShelleyUtxoPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Methods showsPrec ∷ Int → ShelleyUtxoPredFailure era → ShowS # show ∷ ShelleyUtxoPredFailure era → String # showList ∷ [ShelleyUtxoPredFailure era] → ShowS # | |||||
| (Eq (Value era), Eq (TxOut era), Eq (EraRuleFailure "PPUP" era)) ⇒ Eq (ShelleyUtxoPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Methods (==) ∷ ShelleyUtxoPredFailure era → ShelleyUtxoPredFailure era → Bool # (/=) ∷ ShelleyUtxoPredFailure era → ShelleyUtxoPredFailure era → Bool # | |||||
| (NoThunks (Value era), NoThunks (TxOut era), NoThunks (EraRuleFailure "PPUP" era)) ⇒ NoThunks (ShelleyUtxoPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |||||
| type Rep (ShelleyUtxoPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo type Rep (ShelleyUtxoPredFailure era) = D1 ('MetaData "ShelleyUtxoPredFailure" "Cardano.Ledger.Shelley.Rules.Utxo" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (((C1 ('MetaCons "BadInputsUTxO" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set TxIn))) :+: C1 ('MetaCons "ExpiredUTxO" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelLTEQ SlotNo)))) :+: (C1 ('MetaCons "MaxTxSizeUTxO" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelLTEQ Word32))) :+: (C1 ('MetaCons "InputSetEmptyUTxO" 'PrefixI 'False) (U1 ∷ Type → Type) :+: C1 ('MetaCons "FeeTooSmallUTxO" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelGTEQ Coin)))))) :+: ((C1 ('MetaCons "ValueNotConservedUTxO" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelEQ (Value era)))) :+: (C1 ('MetaCons "WrongNetwork" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Network) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set Addr))) :+: C1 ('MetaCons "WrongNetworkWithdrawal" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Network) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set RewardAccount))))) :+: (C1 ('MetaCons "OutputTooSmallUTxO" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxOut era])) :+: (C1 ('MetaCons "UpdateFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (EraRuleFailure "PPUP" era))) :+: C1 ('MetaCons "OutputBootAddrAttrsTooBig" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxOut era])))))) | |||||
Constructors
| TotalDeposits (SafeHash EraIndependentTxBody) Coin | |
| UpdateEvent (Event (EraRule "PPUP" era)) | |
| TxUTxODiff | The UTxOs consumed and created by a signal tx |
Instances
| (Era era, NFData (Event (EraRule "PPUP" era)), NFData (TxOut era)) ⇒ NFData (UtxoEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |||||
| Generic (UtxoEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo Associated Types
| |||||
| (Era era, Eq (TxOut era), Eq (Event (EraRule "PPUP" era))) ⇒ Eq (UtxoEvent era) Source # | |||||
| type Rep (UtxoEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxo type Rep (UtxoEvent era) = D1 ('MetaData "UtxoEvent" "Cardano.Ledger.Shelley.Rules.Utxo" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "TotalDeposits" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SafeHash EraIndependentTxBody)) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin)) :+: (C1 ('MetaCons "UpdateEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "PPUP" era)))) :+: C1 ('MetaCons "TxUTxODiff" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UTxO era)) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (UTxO era))))) | |||||
validSizeComputationCheck ∷ (EraTx era, SafeToHash (TxWits era), Signal (rule era) ~ Tx 'TopTx era) ⇒ Assertion (rule era) Source #
updateUTxOState ∷ (EraTxBody era, EraStake era, EraCertState era, Monad m) ⇒ PParams era → UTxOState era → TxBody 'TopTx 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.
validateInputSetEmptyUTxO ∷ ∀ era (t ∷ TxLevel). EraTxBody era ⇒ TxBody t era → Test (ShelleyUtxoPredFailure era) Source #
Ensure that there is at least one input in the TxBody
txins txb ≠ ∅
validateFeeTooSmallUTxO ∷ EraUTxO era ⇒ PParams era → Tx 'TopTx 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 → 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 ∷ ∀ era (t ∷ TxLevel). EraTxBody era ⇒ Network → TxBody t 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 ∷ ∀ era (l ∷ TxLevel). EraTx era ⇒ PParams era → Tx l 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, EraCertState era) ⇒ PParams era → UTxO era → CertState era → TxBody 'TopTx era → Test (ShelleyUtxoPredFailure era) Source #
Ensure that value consumed and produced matches up exactly
consumed pp utxo txb = produced pp poolParams txb
utxoEnvPParamsL ∷ ∀ era f. Functor f ⇒ (PParams era → f (PParams era)) → UtxoEnv era → f (UtxoEnv era) Source #
utxoEnvCertStateL ∷ ∀ era f. Functor f ⇒ (CertState era → f (CertState era)) → UtxoEnv era → f (UtxoEnv era) Source #
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
data ShelleyUTXOW era Source #
Instances
| (EraTx era, EraUTxO era, ShelleyEraTxBody era, ScriptsNeeded era ~ ShelleyScriptsNeeded era, Embed (EraRule "UTXO" era) (ShelleyUTXOW era), Environment (EraRule "UTXO" era) ~ UtxoEnv era, State (EraRule "UTXO" era) ~ UTxOState era, Signal (EraRule "UTXO" era) ~ Tx 'TopTx era, EraRule "UTXOW" era ~ ShelleyUTXOW era, InjectRuleFailure "UTXOW" ShelleyUtxowPredFailure era, EraGov era, EraCertState era) ⇒ STS (ShelleyUTXOW era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Associated Types
Methods initialRules ∷ [InitialRule (ShelleyUTXOW era)] Source # transitionRules ∷ [TransitionRule (ShelleyUTXOW era)] Source # assertions ∷ [Assertion (ShelleyUTXOW era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyUTXOW era) → String Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyUTXO era), PredicateFailure (EraRule "UTXO" era) ~ ShelleyUtxoPredFailure era, Event (EraRule "UTXO" era) ~ UtxoEvent era) ⇒ Embed (ShelleyUTXO era) (ShelleyUTXOW era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Methods wrapFailed ∷ PredicateFailure (ShelleyUTXO era) → PredicateFailure (ShelleyUTXOW era) Source # wrapEvent ∷ Event (ShelleyUTXO era) → Event (ShelleyUTXOW era) Source # | |||||||||||||||||||||||||
| (STS (ShelleyUTXOW era), PredicateFailure (EraRule "UTXOW" era) ~ ShelleyUtxowPredFailure era, Event (EraRule "UTXOW" era) ~ Event (ShelleyUTXOW era)) ⇒ Embed (ShelleyUTXOW era) (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods wrapFailed ∷ PredicateFailure (ShelleyUTXOW era) → PredicateFailure (ShelleyLEDGER era) Source # wrapEvent ∷ Event (ShelleyUTXOW era) → Event (ShelleyLEDGER era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyUTXOW era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |||||||||||||||||||||||||
| type Environment (ShelleyUTXOW era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |||||||||||||||||||||||||
| type Event (ShelleyUTXOW era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyUTXOW era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |||||||||||||||||||||||||
| type Signal (ShelleyUTXOW era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |||||||||||||||||||||||||
| type State (ShelleyUTXOW era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |||||||||||||||||||||||||
data ShelleyUtxowPredFailure era Source #
Constructors
| InvalidWitnessesUTXOW [VKey 'Witness] | |
| MissingVKeyWitnessesUTXOW (Set (KeyHash 'Witness)) | |
| MissingScriptWitnessesUTXOW (Set ScriptHash) | |
| ScriptWitnessNotValidatingUTXOW (Set ScriptHash) | |
| UtxoFailure (PredicateFailure (EraRule "UTXO" era)) | |
| MIRInsufficientGenesisSigsUTXOW (Set (KeyHash 'Witness)) | |
| MissingTxBodyMetadataHash TxAuxDataHash | |
| MissingTxMetadata TxAuxDataHash | |
| ConflictingMetadataHash (Mismatch 'RelEQ TxAuxDataHash) | |
| InvalidMetadata | |
| ExtraneousScriptWitnessesUTXOW (Set ScriptHash) |
Instances
| InjectRuleFailure "BBODY" ShelleyUtxowPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Bbody Methods injectFailure ∷ ShelleyUtxowPredFailure ShelleyEra → EraRuleFailure "BBODY" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGER" ShelleyUtxowPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledger Methods injectFailure ∷ ShelleyUtxowPredFailure ShelleyEra → EraRuleFailure "LEDGER" ShelleyEra Source # | |||||
| InjectRuleFailure "LEDGERS" ShelleyUtxowPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Ledgers Methods injectFailure ∷ ShelleyUtxowPredFailure ShelleyEra → EraRuleFailure "LEDGERS" ShelleyEra Source # | |||||
| InjectRuleFailure "UTXOW" ShelleyUtxowPredFailure ShelleyEra Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Methods injectFailure ∷ ShelleyUtxowPredFailure ShelleyEra → EraRuleFailure "UTXOW" ShelleyEra Source # | |||||
| (Era era, DecCBOR (PredicateFailure (EraRule "UTXO" era)), Typeable (Script era), Typeable (TxAuxData era)) ⇒ DecCBOR (ShelleyUtxowPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |||||
| (Era era, EncCBOR (PredicateFailure (EraRule "UTXO" era))) ⇒ EncCBOR (ShelleyUtxowPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Methods encCBOR ∷ ShelleyUtxowPredFailure era → Encoding Source # | |||||
| (NFData (PredicateFailure (EraRule "UTXO" era)), Era era) ⇒ NFData (ShelleyUtxowPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Methods rnf ∷ ShelleyUtxowPredFailure era → () # | |||||
| Generic (ShelleyUtxowPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Associated Types
Methods from ∷ ShelleyUtxowPredFailure era → Rep (ShelleyUtxowPredFailure era) x # to ∷ Rep (ShelleyUtxowPredFailure era) x → ShelleyUtxowPredFailure era # | |||||
| (Show (PredicateFailure (EraRule "UTXO" era)), Era era) ⇒ Show (ShelleyUtxowPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Methods showsPrec ∷ Int → ShelleyUtxowPredFailure era → ShowS # show ∷ ShelleyUtxowPredFailure era → String # showList ∷ [ShelleyUtxowPredFailure era] → ShowS # | |||||
| (Eq (PredicateFailure (EraRule "UTXO" era)), Era era) ⇒ Eq (ShelleyUtxowPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Methods (==) ∷ ShelleyUtxowPredFailure era → ShelleyUtxowPredFailure era → Bool # (/=) ∷ ShelleyUtxowPredFailure era → ShelleyUtxowPredFailure era → Bool # | |||||
| (NoThunks (PredicateFailure (EraRule "UTXO" era)), Era era) ⇒ NoThunks (ShelleyUtxowPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |||||
| type Rep (ShelleyUtxowPredFailure era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow type Rep (ShelleyUtxowPredFailure era) = D1 ('MetaData "ShelleyUtxowPredFailure" "Cardano.Ledger.Shelley.Rules.Utxow" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (((C1 ('MetaCons "InvalidWitnessesUTXOW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [VKey 'Witness])) :+: C1 ('MetaCons "MissingVKeyWitnessesUTXOW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set (KeyHash 'Witness))))) :+: (C1 ('MetaCons "MissingScriptWitnessesUTXOW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set ScriptHash))) :+: (C1 ('MetaCons "ScriptWitnessNotValidatingUTXOW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set ScriptHash))) :+: C1 ('MetaCons "UtxoFailure" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PredicateFailure (EraRule "UTXO" era))))))) :+: ((C1 ('MetaCons "MIRInsufficientGenesisSigsUTXOW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set (KeyHash 'Witness)))) :+: (C1 ('MetaCons "MissingTxBodyMetadataHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxAuxDataHash)) :+: C1 ('MetaCons "MissingTxMetadata" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxAuxDataHash)))) :+: (C1 ('MetaCons "ConflictingMetadataHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Mismatch 'RelEQ TxAuxDataHash))) :+: (C1 ('MetaCons "InvalidMetadata" 'PrefixI 'False) (U1 ∷ Type → Type) :+: C1 ('MetaCons "ExtraneousScriptWitnessesUTXOW" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set ScriptHash))))))) | |||||
newtype ShelleyUtxowEvent era Source #
Instances
| NFData (Event (EraRule "UTXO" era)) ⇒ NFData (ShelleyUtxowEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Methods rnf ∷ ShelleyUtxowEvent era → () # | |||||
| Generic (ShelleyUtxowEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Associated Types
Methods from ∷ ShelleyUtxowEvent era → Rep (ShelleyUtxowEvent era) x # to ∷ Rep (ShelleyUtxowEvent era) x → ShelleyUtxowEvent era # | |||||
| Eq (Event (EraRule "UTXO" era)) ⇒ Eq (ShelleyUtxowEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow Methods (==) ∷ ShelleyUtxowEvent era → ShelleyUtxowEvent era → Bool # (/=) ∷ ShelleyUtxowEvent era → ShelleyUtxowEvent era → Bool # | |||||
| type Rep (ShelleyUtxowEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Utxow type Rep (ShelleyUtxowEvent era) = D1 ('MetaData "ShelleyUtxowEvent" "Cardano.Ledger.Shelley.Rules.Utxow" "cardano-ledger-shelley-1.18.0.0-inplace" 'True) (C1 ('MetaCons "UtxoEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "UTXO" era))))) | |||||
transitionRulesUTXOW ∷ (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 'TopTx era, Environment (EraRule "UTXOW" era) ~ UtxoEnv era, State (EraRule "UTXOW" era) ~ UTxOState era, Signal (EraRule "UTXOW" era) ~ Tx 'TopTx era, InjectRuleFailure "UTXOW" ShelleyUtxowPredFailure era, STS (EraRule "UTXOW" era), EraCertState era) ⇒ 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.
validateFailedNativeScripts ∷ ∀ era (l ∷ TxLevel). EraTx era ⇒ ScriptsProvided era → Tx l era → Test (ShelleyUtxowPredFailure era) Source #
validateMissingScripts ∷ ShelleyScriptsNeeded era → ScriptsProvided era → Test (ShelleyUtxowPredFailure era) Source #
validateVerifiedWits ∷ ∀ era (l ∷ TxLevel). EraTx era ⇒ Tx l era → Test (ShelleyUtxowPredFailure era) Source #
Determine if the UTxO witnesses in a given transaction are correct.
validateMetadata ∷ ∀ era (l ∷ TxLevel). EraTx era ⇒ PParams era → Tx l era → Test (ShelleyUtxowPredFailure era) Source #
check metadata hash ((adh = ◇) ∧ (ad= ◇)) ∨ (adh = hashAD ad)
validateMIRInsufficientGenesisSigs ∷ (EraTx era, ShelleyEraTxBody era) ⇒ GenDelegs → Word64 → Set (KeyHash 'Witness) → Tx 'TopTx 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 #
Arguments
| ∷ ∀ era (t ∷ TxLevel). EraUTxO era | |
| ⇒ Set (KeyHash 'Witness) | Provided witness |
| → CertState era | |
| → UTxO era | |
| → TxBody t era | |
| → Test (ShelleyUtxowPredFailure era) |
Verify that we provide at least all of the required witnesses
witsVKeyNeeded utxo tx ⊆ witsKeyHashes
Tick
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
data ShelleyEPOCH era Source #
Instances
| (EraTxOut era, EraGov era, EraStake era, EraCertState era, GovState era ~ ShelleyGovState era, Embed (EraRule "SNAP" era) (ShelleyEPOCH era), Environment (EraRule "SNAP" era) ~ SnapEnv era, State (EraRule "SNAP" era) ~ SnapShots, Signal (EraRule "SNAP" era) ~ (), Embed (EraRule "POOLREAP" era) (ShelleyEPOCH era), Environment (EraRule "POOLREAP" era) ~ (), State (EraRule "POOLREAP" era) ~ ShelleyPoolreapState era, Signal (EraRule "POOLREAP" era) ~ EpochNo, Embed (EraRule "UPEC" era) (ShelleyEPOCH era), Environment (EraRule "UPEC" era) ~ LedgerState era, State (EraRule "UPEC" era) ~ UpecState era, Signal (EraRule "UPEC" era) ~ (), Default (PParams era)) ⇒ STS (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch Associated Types
Methods initialRules ∷ [InitialRule (ShelleyEPOCH era)] Source # transitionRules ∷ [TransitionRule (ShelleyEPOCH era)] Source # assertions ∷ [Assertion (ShelleyEPOCH era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyEPOCH era) → String Source # | |||||||||||||||||||||||||
| (STS (ShelleyEPOCH era), Event (EraRule "EPOCH" era) ~ ShelleyEpochEvent era) ⇒ Embed (ShelleyEPOCH era) (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch Methods wrapFailed ∷ PredicateFailure (ShelleyEPOCH era) → PredicateFailure (ShelleyNEWEPOCH era) Source # wrapEvent ∷ Event (ShelleyEPOCH era) → Event (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyPOOLREAP era), Event (EraRule "POOLREAP" era) ~ ShelleyPoolreapEvent era) ⇒ Embed (ShelleyPOOLREAP era) (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch Methods wrapFailed ∷ PredicateFailure (ShelleyPOOLREAP era) → PredicateFailure (ShelleyEPOCH era) Source # wrapEvent ∷ Event (ShelleyPOOLREAP era) → Event (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
| (EraTxOut era, EraStake era, Event (EraRule "SNAP" era) ~ SnapEvent era, EraCertState era) ⇒ Embed (ShelleySNAP era) (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch Methods wrapFailed ∷ PredicateFailure (ShelleySNAP era) → PredicateFailure (ShelleyEPOCH era) Source # wrapEvent ∷ Event (ShelleySNAP era) → Event (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyUPEC era), Event (EraRule "UPEC" era) ~ Void) ⇒ Embed (ShelleyUPEC era) (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch Methods wrapFailed ∷ PredicateFailure (ShelleyUPEC era) → PredicateFailure (ShelleyEPOCH era) Source # wrapEvent ∷ Event (ShelleyUPEC era) → Event (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |||||||||||||||||||||||||
| type Environment (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |||||||||||||||||||||||||
| type Event (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |||||||||||||||||||||||||
| type Signal (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |||||||||||||||||||||||||
| type State (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |||||||||||||||||||||||||
data ShelleyEpochEvent era Source #
Constructors
| PoolReapEvent (Event (EraRule "POOLREAP" era)) | |
| SnapEvent (Event (EraRule "SNAP" era)) | |
| UpecEvent (Event (EraRule "UPEC" era)) |
Instances
| (NFData (Event (EraRule "POOLREAP" era)), NFData (Event (EraRule "SNAP" era)), NFData (Event (EraRule "UPEC" era))) ⇒ NFData (ShelleyEpochEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch Methods rnf ∷ ShelleyEpochEvent era → () # | |||||
| Generic (ShelleyEpochEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch Associated Types
Methods from ∷ ShelleyEpochEvent era → Rep (ShelleyEpochEvent era) x # to ∷ Rep (ShelleyEpochEvent era) x → ShelleyEpochEvent era # | |||||
| (Eq (Event (EraRule "POOLREAP" era)), Eq (Event (EraRule "SNAP" era)), Eq (Event (EraRule "UPEC" era))) ⇒ Eq (ShelleyEpochEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch Methods (==) ∷ ShelleyEpochEvent era → ShelleyEpochEvent era → Bool # (/=) ∷ ShelleyEpochEvent era → ShelleyEpochEvent era → Bool # | |||||
| type Rep (ShelleyEpochEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch type Rep (ShelleyEpochEvent era) = D1 ('MetaData "ShelleyEpochEvent" "Cardano.Ledger.Shelley.Rules.Epoch" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "PoolReapEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "POOLREAP" era)))) :+: (C1 ('MetaCons "SnapEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "SNAP" era)))) :+: C1 ('MetaCons "UpecEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "UPEC" era)))))) | |||||
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
data ShelleyNEWEPOCH era Source #
Instances
| (EraTxOut era, EraGov era, EraStake era, EraCertState era, Embed (EraRule "MIR" era) (ShelleyNEWEPOCH era), Embed (EraRule "EPOCH" era) (ShelleyNEWEPOCH era), Environment (EraRule "MIR" era) ~ (), State (EraRule "MIR" era) ~ EpochState era, Signal (EraRule "MIR" era) ~ (), Event (EraRule "RUPD" era) ~ RupdEvent, Environment (EraRule "EPOCH" era) ~ (), State (EraRule "EPOCH" era) ~ EpochState era, Signal (EraRule "EPOCH" era) ~ EpochNo, Default (EpochState era), Default (State (EraRule "PPUP" era)), Default (PParams era), Default (StashedAVVMAddresses era)) ⇒ STS (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch Associated Types
Methods initialRules ∷ [InitialRule (ShelleyNEWEPOCH era)] Source # transitionRules ∷ [TransitionRule (ShelleyNEWEPOCH era)] Source # assertions ∷ [Assertion (ShelleyNEWEPOCH era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyNEWEPOCH era) → String Source # | |||||||||||||||||||||||||
| (STS (ShelleyEPOCH era), Event (EraRule "EPOCH" era) ~ ShelleyEpochEvent era) ⇒ Embed (ShelleyEPOCH era) (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch Methods wrapFailed ∷ PredicateFailure (ShelleyEPOCH era) → PredicateFailure (ShelleyNEWEPOCH era) Source # wrapEvent ∷ Event (ShelleyEPOCH era) → Event (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
| (EraGov era, EraCertState era, Default (EpochState era), Event (EraRule "MIR" era) ~ ShelleyMirEvent era) ⇒ Embed (ShelleyMIR era) (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch Methods wrapFailed ∷ PredicateFailure (ShelleyMIR era) → PredicateFailure (ShelleyNEWEPOCH era) Source # wrapEvent ∷ Event (ShelleyMIR era) → Event (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
| (STS (ShelleyNEWEPOCH era), Event (EraRule "NEWEPOCH" era) ~ ShelleyNewEpochEvent era) ⇒ Embed (ShelleyNEWEPOCH era) (ShelleyTICK era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Methods wrapFailed ∷ PredicateFailure (ShelleyNEWEPOCH era) → PredicateFailure (ShelleyTICK era) Source # wrapEvent ∷ Event (ShelleyNEWEPOCH era) → Event (ShelleyTICK era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |||||||||||||||||||||||||
| type Environment (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |||||||||||||||||||||||||
| type Event (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |||||||||||||||||||||||||
| type Signal (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |||||||||||||||||||||||||
| type State (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |||||||||||||||||||||||||
data ShelleyNewEpochEvent era Source #
Constructors
| DeltaRewardEvent (Event (EraRule "RUPD" era)) | |
| RestrainedRewards EpochNo (Map (Credential 'Staking) (Set Reward)) (Set (Credential 'Staking)) | |
| TotalRewardEvent EpochNo (Map (Credential 'Staking) (Set Reward)) | |
| EpochEvent (Event (EraRule "EPOCH" era)) | |
| MirEvent (Event (EraRule "MIR" era)) | |
| TotalAdaPotsEvent AdaPots |
Instances
| (NFData (Event (EraRule "EPOCH" era)), NFData (Event (EraRule "MIR" era)), NFData (Event (EraRule "RUPD" era))) ⇒ NFData (ShelleyNewEpochEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch Methods rnf ∷ ShelleyNewEpochEvent era → () # | |||||
| Generic (ShelleyNewEpochEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch Associated Types
Methods from ∷ ShelleyNewEpochEvent era → Rep (ShelleyNewEpochEvent era) x # to ∷ Rep (ShelleyNewEpochEvent era) x → ShelleyNewEpochEvent era # | |||||
| (Eq (Event (EraRule "EPOCH" era)), Eq (Event (EraRule "MIR" era)), Eq (Event (EraRule "RUPD" era))) ⇒ Eq (ShelleyNewEpochEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch Methods (==) ∷ ShelleyNewEpochEvent era → ShelleyNewEpochEvent era → Bool # (/=) ∷ ShelleyNewEpochEvent era → ShelleyNewEpochEvent era → Bool # | |||||
| type Rep (ShelleyNewEpochEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch type Rep (ShelleyNewEpochEvent era) = D1 ('MetaData "ShelleyNewEpochEvent" "Cardano.Ledger.Shelley.Rules.NewEpoch" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) ((C1 ('MetaCons "DeltaRewardEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "RUPD" era)))) :+: (C1 ('MetaCons "RestrainedRewards" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochNo) :*: (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (Credential 'Staking) (Set Reward))) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set (Credential 'Staking))))) :+: C1 ('MetaCons "TotalRewardEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochNo) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (Credential 'Staking) (Set Reward)))))) :+: (C1 ('MetaCons "EpochEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "EPOCH" era)))) :+: (C1 ('MetaCons "MirEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "MIR" era)))) :+: C1 ('MetaCons "TotalAdaPotsEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 AdaPots))))) | |||||
updateRewards ∷ (EraGov era, EraCertState era) ⇒ EpochState era → EpochNo → RewardUpdate → Rule (ShelleyNEWEPOCH era) 'Transition (EpochState era) Source #
Identity functor and monad. (a non-strict monad)
Examples
>>>fmap (+1) (Identity 0)Identity 1
>>>Identity [1, 2, 3] <> Identity [4, 5, 6]Identity [1,2,3,4,5,6]
>>> do
x <- Identity 10
y <- Identity (x + 5)
pure (x + y)
Identity 25
Since: base-4.8.0.0
Constructors
| Identity | |
Fields
| |
Instances
| Representable Identity | |||||
| FromJSON1 Identity | |||||
Defined in Data.Aeson.Types.FromJSON | |||||
| ToJSON1 Identity | |||||
Defined in Data.Aeson.Types.ToJSON Methods liftToJSON ∷ (a → Bool) → (a → Value) → ([a] → Value) → Identity a → Value Source # liftToJSONList ∷ (a → Bool) → (a → Value) → ([a] → Value) → [Identity a] → Value Source # liftToEncoding ∷ (a → Bool) → (a → Encoding) → ([a] → Encoding) → Identity a → Encoding Source # liftToEncodingList ∷ (a → Bool) → (a → Encoding) → ([a] → Encoding) → [Identity a] → Encoding Source # | |||||
| MonadZip Identity | Since: base-4.8.0.0 | ||||
| Foldable1 Identity | Since: base-4.18.0.0 | ||||
Defined in Data.Foldable1 Methods fold1 ∷ Semigroup m ⇒ Identity m → m # foldMap1 ∷ Semigroup m ⇒ (a → m) → Identity a → m # foldMap1' ∷ Semigroup m ⇒ (a → m) → Identity a → m # toNonEmpty ∷ Identity a → NonEmpty a # maximum ∷ Ord a ⇒ Identity a → a # minimum ∷ Ord a ⇒ Identity a → a # foldrMap1 ∷ (a → b) → (a → b → b) → Identity a → b # foldlMap1' ∷ (a → b) → (b → a → b) → Identity a → b # foldlMap1 ∷ (a → b) → (b → a → b) → Identity a → b # foldrMap1' ∷ (a → b) → (a → b → b) → Identity a → b # | |||||
| Eq1 Identity | Since: base-4.9.0.0 | ||||
| Ord1 Identity | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Classes | |||||
| Read1 Identity | Since: base-4.9.0.0 | ||||
Defined in Data.Functor.Classes | |||||
| Show1 Identity | Since: base-4.9.0.0 | ||||
| DecCBOR Pulser Source # | |||||
| EncCBOR Pulser Source # | |||||
| HKDApplicative Identity | |||||
| HKDFunctor Identity | |||||
Defined in Cardano.Ledger.HKD | |||||
| NFData Pulser Source # | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate | |||||
| NFData1 Identity | Since: deepseq-1.4.3.0 | ||||
Defined in Control.DeepSeq | |||||
| Applicative Identity | Since: base-4.8.0.0 | ||||
| Functor Identity | Since: base-4.8.0.0 | ||||
| Monad Identity | Since: base-4.8.0.0 | ||||
| MonadFix Identity | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity | |||||
| Foldable Identity | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity Methods fold ∷ Monoid m ⇒ Identity m → m # foldMap ∷ Monoid m ⇒ (a → m) → Identity a → m # foldMap' ∷ Monoid m ⇒ (a → m) → Identity a → m # foldr ∷ (a → b → b) → b → Identity a → b # foldr' ∷ (a → b → b) → b → Identity a → b # foldl ∷ (b → a → b) → b → Identity a → b # foldl' ∷ (b → a → b) → b → Identity a → b # foldr1 ∷ (a → a → a) → Identity a → a # foldl1 ∷ (a → a → a) → Identity a → a # elem ∷ Eq a ⇒ a → Identity a → Bool # maximum ∷ Ord a ⇒ Identity a → a # minimum ∷ Ord a ⇒ Identity a → a # | |||||
| Foldable Node | |||||
Defined in Hedgehog.Internal.Tree Methods fold ∷ Monoid m ⇒ Node m → m # foldMap ∷ Monoid m ⇒ (a → m) → Node a → m # foldMap' ∷ Monoid m ⇒ (a → m) → Node a → m # foldr ∷ (a → b → b) → b → Node a → b # foldr' ∷ (a → b → b) → b → Node a → b # foldl ∷ (b → a → b) → b → Node a → b # foldl' ∷ (b → a → b) → b → Node a → b # foldr1 ∷ (a → a → a) → Node a → a # foldl1 ∷ (a → a → a) → Node a → a # elem ∷ Eq a ⇒ a → Node a → Bool # maximum ∷ Ord a ⇒ Node a → a # | |||||
| Foldable Tree | |||||
Defined in Hedgehog.Internal.Tree Methods fold ∷ Monoid m ⇒ Tree m → m # foldMap ∷ Monoid m ⇒ (a → m) → Tree a → m # foldMap' ∷ Monoid m ⇒ (a → m) → Tree a → m # foldr ∷ (a → b → b) → b → Tree a → b # foldr' ∷ (a → b → b) → b → Tree a → b # foldl ∷ (b → a → b) → b → Tree a → b # foldl' ∷ (b → a → b) → b → Tree a → b # foldr1 ∷ (a → a → a) → Tree a → a # foldl1 ∷ (a → a → a) → Tree a → a # elem ∷ Eq a ⇒ a → Tree a → Bool # maximum ∷ Ord a ⇒ Tree a → a # | |||||
| Traversable Identity | Since: base-4.9.0.0 | ||||
| Traversable Node | |||||
| Traversable Tree | |||||
| Hashable1 Identity | |||||
Defined in Data.Hashable.Class | |||||
| NoThunks Pulser Source # | |||||
| Generic1 Identity | |||||
Defined in GHC.Internal.Data.Functor.Identity Associated Types
| |||||
| MonadBaseControl Identity Identity | |||||
| Cosieve ReifiedGetter Identity | |||||
Defined in Control.Lens.Reified Methods cosieve ∷ ReifiedGetter a b → Identity a → b Source # | |||||
| Sieve ReifiedGetter Identity | |||||
Defined in Control.Lens.Reified Methods sieve ∷ ReifiedGetter a b → a → Identity b Source # | |||||
| PrettyBy config a ⇒ DefaultPrettyBy config (Identity a) | |||||
Defined in Text.PrettyBy.Internal Methods defaultPrettyBy ∷ config → Identity a → Doc ann Source # defaultPrettyListBy ∷ config → [Identity a] → Doc ann Source # | |||||
| PrettyDefaultBy config (Identity a) ⇒ PrettyBy config (Identity a) |
| ||||
| Lift a ⇒ Lift (Identity a ∷ Type) | |||||
| Unbox a ⇒ Vector Vector (Identity a) | |||||
Defined in Data.Vector.Unboxed.Base Methods basicUnsafeFreeze ∷ Mutable Vector s (Identity a) → ST s (Vector (Identity a)) Source # basicUnsafeThaw ∷ Vector (Identity a) → ST s (Mutable Vector s (Identity a)) Source # basicLength ∷ Vector (Identity a) → Int Source # basicUnsafeSlice ∷ Int → Int → Vector (Identity a) → Vector (Identity a) Source # basicUnsafeIndexM ∷ Vector (Identity a) → Int → Box (Identity a) Source # basicUnsafeCopy ∷ Mutable Vector s (Identity a) → Vector (Identity a) → ST s () Source # | |||||
| Unbox a ⇒ MVector MVector (Identity a) | |||||
Defined in Data.Vector.Unboxed.Base Methods basicLength ∷ MVector s (Identity a) → Int Source # basicUnsafeSlice ∷ Int → Int → MVector s (Identity a) → MVector s (Identity a) Source # basicOverlaps ∷ MVector s (Identity a) → MVector s (Identity a) → Bool Source # basicUnsafeNew ∷ Int → ST s (MVector s (Identity a)) Source # basicInitialize ∷ MVector s (Identity a) → ST s () Source # basicUnsafeReplicate ∷ Int → Identity a → ST s (MVector s (Identity a)) Source # basicUnsafeRead ∷ MVector s (Identity a) → Int → ST s (Identity a) Source # basicUnsafeWrite ∷ MVector s (Identity a) → Int → Identity a → ST s () Source # basicClear ∷ MVector s (Identity a) → ST s () Source # basicSet ∷ MVector s (Identity a) → Identity a → ST s () Source # basicUnsafeCopy ∷ MVector s (Identity a) → MVector s (Identity a) → ST s () Source # basicUnsafeMove ∷ MVector s (Identity a) → MVector s (Identity a) → ST s () Source # basicUnsafeGrow ∷ MVector s (Identity a) → Int → ST s (MVector s (Identity a)) Source # | |||||
| Monoid w ⇒ MonadAccum w (AccumT w Identity) | Since: mtl-2.3 | ||||
| MonadSelect r (SelectT r Identity) | Since: mtl-2.3 | ||||
Defined in Control.Monad.Select | |||||
| FromJSON a ⇒ FromJSON (Identity a) | |||||
| FromJSON (CekMachineCostsBase Identity) | |||||
| FromJSONKey a ⇒ FromJSONKey (Identity a) | |||||
Defined in Data.Aeson.Types.FromJSON Methods | |||||
| ToJSON a ⇒ ToJSON (Identity a) | |||||
| ToJSON (CekMachineCostsBase Identity) | |||||
Defined in UntypedPlutusCore.Evaluation.Machine.Cek.CekMachineCosts | |||||
| ToJSONKey a ⇒ ToJSONKey (Identity a) | |||||
Defined in Data.Aeson.Types.ToJSON Methods | |||||
| Default a ⇒ Default (Identity a) | |||||
Defined in Data.Default.Internal | |||||
| NFData a ⇒ NFData (Identity a) | Since: deepseq-1.4.0.0 | ||||
Defined in Control.DeepSeq | |||||
| Monoid a ⇒ Monoid (Identity a) | Since: base-4.9.0.0 | ||||
| Semigroup a ⇒ Semigroup (Identity a) | Since: base-4.9.0.0 | ||||
| Bits a ⇒ Bits (Identity a) | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity Methods (.&.) ∷ Identity a → Identity a → Identity a # (.|.) ∷ Identity a → Identity a → Identity a # xor ∷ Identity a → Identity a → Identity a # complement ∷ Identity a → Identity a # shift ∷ Identity a → Int → Identity a # rotate ∷ Identity a → Int → Identity a # setBit ∷ Identity a → Int → Identity a # clearBit ∷ Identity a → Int → Identity a # complementBit ∷ Identity a → Int → Identity a # testBit ∷ Identity a → Int → Bool # bitSizeMaybe ∷ Identity a → Maybe Int # isSigned ∷ Identity a → Bool # shiftL ∷ Identity a → Int → Identity a # unsafeShiftL ∷ Identity a → Int → Identity a # shiftR ∷ Identity a → Int → Identity a # unsafeShiftR ∷ Identity a → Int → Identity a # rotateL ∷ Identity a → Int → Identity a # | |||||
| FiniteBits a ⇒ FiniteBits (Identity a) | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity Methods finiteBitSize ∷ Identity a → Int # countLeadingZeros ∷ Identity a → Int # countTrailingZeros ∷ Identity a → Int # | |||||
| IsString a ⇒ IsString (Identity a) | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.String Methods fromString ∷ String → Identity a # | |||||
| Bounded a ⇒ Bounded (Identity a) | Since: base-4.9.0.0 | ||||
| Enum a ⇒ Enum (Identity a) | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity | |||||
| Floating a ⇒ Floating (Identity a) | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity Methods exp ∷ Identity a → Identity a # log ∷ Identity a → Identity a # sqrt ∷ Identity a → Identity a # (**) ∷ Identity a → Identity a → Identity a # logBase ∷ Identity a → Identity a → Identity a # sin ∷ Identity a → Identity a # cos ∷ Identity a → Identity a # tan ∷ Identity a → Identity a # asin ∷ Identity a → Identity a # acos ∷ Identity a → Identity a # atan ∷ Identity a → Identity a # sinh ∷ Identity a → Identity a # cosh ∷ Identity a → Identity a # tanh ∷ Identity a → Identity a # asinh ∷ Identity a → Identity a # acosh ∷ Identity a → Identity a # atanh ∷ Identity a → Identity a # log1p ∷ Identity a → Identity a # expm1 ∷ Identity a → Identity a # | |||||
| RealFloat a ⇒ RealFloat (Identity a) | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity Methods floatRadix ∷ Identity a → Integer # floatDigits ∷ Identity a → Int # floatRange ∷ Identity a → (Int, Int) # decodeFloat ∷ Identity a → (Integer, Int) # encodeFloat ∷ Integer → Int → Identity a # significand ∷ Identity a → Identity a # scaleFloat ∷ Int → Identity a → Identity a # isInfinite ∷ Identity a → Bool # isDenormalized ∷ Identity a → Bool # isNegativeZero ∷ Identity a → Bool # | |||||
| Storable a ⇒ Storable (Identity a) | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity | |||||
| Generic (Identity a) | |||||
Defined in GHC.Internal.Data.Functor.Identity Associated Types
| |||||
| Ix a ⇒ Ix (Identity a) | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity Methods range ∷ (Identity a, Identity a) → [Identity a] # index ∷ (Identity a, Identity a) → Identity a → Int # unsafeIndex ∷ (Identity a, Identity a) → Identity a → Int # inRange ∷ (Identity a, Identity a) → Identity a → Bool # rangeSize ∷ (Identity a, Identity a) → Int # unsafeRangeSize ∷ (Identity a, Identity a) → Int # | |||||
| Num a ⇒ Num (Identity a) | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity | |||||
| Read a ⇒ Read (Identity a) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 | ||||
| Fractional a ⇒ Fractional (Identity a) | Since: base-4.9.0.0 | ||||
| Integral a ⇒ Integral (Identity a) | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity Methods quot ∷ Identity a → Identity a → Identity a # rem ∷ Identity a → Identity a → Identity a # div ∷ Identity a → Identity a → Identity a # mod ∷ Identity a → Identity a → Identity a # quotRem ∷ Identity a → Identity a → (Identity a, Identity a) # divMod ∷ Identity a → Identity a → (Identity a, Identity a) # | |||||
| Real a ⇒ Real (Identity a) | Since: base-4.9.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity Methods toRational ∷ Identity a → Rational # | |||||
| RealFrac a ⇒ RealFrac (Identity a) | Since: base-4.9.0.0 | ||||
| Show a ⇒ Show (Identity a) | This instance would be equivalent to the derived instances of the
Since: base-4.8.0.0 | ||||
| Eq a ⇒ Eq (Identity a) | Since: base-4.8.0.0 | ||||
| Ord a ⇒ Ord (Identity a) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity | |||||
| Abelian a ⇒ Abelian (Identity a) | |||||
Defined in Data.Group | |||||
| Cyclic a ⇒ Cyclic (Identity a) | |||||
Defined in Data.Group | |||||
| Group a ⇒ Group (Identity a) |
| ||||
| Hashable a ⇒ Hashable (Identity a) | |||||
| Ixed (Identity a) | |||||
Defined in Control.Lens.At | |||||
| Wrapped (Identity a) | |||||
| MonoFoldable (Identity a) | |||||
Defined in Data.MonoTraversable Methods ofoldMap ∷ Monoid m ⇒ (Element (Identity a) → m) → Identity a → m Source # ofoldr ∷ (Element (Identity a) → b → b) → b → Identity a → b Source # ofoldl' ∷ (a0 → Element (Identity a) → a0) → a0 → Identity a → a0 Source # otoList ∷ Identity a → [Element (Identity a)] Source # oall ∷ (Element (Identity a) → Bool) → Identity a → Bool Source # oany ∷ (Element (Identity a) → Bool) → Identity a → Bool Source # onull ∷ Identity a → Bool Source # olength ∷ Identity a → Int Source # olength64 ∷ Identity a → Int64 Source # ocompareLength ∷ Integral i ⇒ Identity a → i → Ordering Source # otraverse_ ∷ Applicative f ⇒ (Element (Identity a) → f b) → Identity a → f () Source # ofor_ ∷ Applicative f ⇒ Identity a → (Element (Identity a) → f b) → f () Source # omapM_ ∷ Applicative m ⇒ (Element (Identity a) → m ()) → Identity a → m () Source # oforM_ ∷ Applicative m ⇒ Identity a → (Element (Identity a) → m ()) → m () Source # ofoldlM ∷ Monad m ⇒ (a0 → Element (Identity a) → m a0) → a0 → Identity a → m a0 Source # ofoldMap1Ex ∷ Semigroup m ⇒ (Element (Identity a) → m) → Identity a → m Source # ofoldr1Ex ∷ (Element (Identity a) → Element (Identity a) → Element (Identity a)) → Identity a → Element (Identity a) Source # ofoldl1Ex' ∷ (Element (Identity a) → Element (Identity a) → Element (Identity a)) → Identity a → Element (Identity a) Source # headEx ∷ Identity a → Element (Identity a) Source # lastEx ∷ Identity a → Element (Identity a) Source # unsafeHead ∷ Identity a → Element (Identity a) Source # unsafeLast ∷ Identity a → Element (Identity a) Source # maximumByEx ∷ (Element (Identity a) → Element (Identity a) → Ordering) → Identity a → Element (Identity a) Source # minimumByEx ∷ (Element (Identity a) → Element (Identity a) → Ordering) → Identity a → Element (Identity a) Source # oelem ∷ Element (Identity a) → Identity a → Bool Source # onotElem ∷ Element (Identity a) → Identity a → Bool Source # | |||||
| MonoFunctor (Identity a) | |||||
| MonoPointed (Identity a) | |||||
| MonoTraversable (Identity a) | |||||
| NoThunks a ⇒ NoThunks (Identity a) | |||||
| Flat a ⇒ Flat (Identity a) | Since: plutus-core-0.4.4 | ||||
| Pretty a ⇒ Pretty (Identity a) |
| ||||
| Prim a ⇒ Prim (Identity a) | Since: primitive-0.6.5.0 | ||||
Defined in Data.Primitive.Types Methods sizeOfType# ∷ Proxy (Identity a) → Int# Source # sizeOf# ∷ Identity a → Int# Source # alignmentOfType# ∷ Proxy (Identity a) → Int# Source # alignment# ∷ Identity a → Int# Source # indexByteArray# ∷ ByteArray# → Int# → Identity a Source # readByteArray# ∷ MutableByteArray# s → Int# → State# s → (# State# s, Identity a #) Source # writeByteArray# ∷ MutableByteArray# s → Int# → Identity a → State# s → State# s Source # setByteArray# ∷ MutableByteArray# s → Int# → Int# → Identity a → State# s → State# s Source # indexOffAddr# ∷ Addr# → Int# → Identity a Source # readOffAddr# ∷ Addr# → Int# → State# s → (# State# s, Identity a #) Source # writeOffAddr# ∷ Addr# → Int# → Identity a → State# s → State# s Source # setOffAddr# ∷ Addr# → Int# → Int# → Identity a → State# s → State# s Source # | |||||
| Unbox a ⇒ Unbox (Identity a) | |||||
Defined in Data.Vector.Unboxed.Base | |||||
| t ~ Identity b ⇒ Rewrapped (Identity a) t | |||||
Defined in Control.Lens.Wrapped | |||||
| Field1 (Identity a) (Identity b) a b | |||||
| NFData (ShelleyPParams Identity era) Source # | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods rnf ∷ ShelleyPParams Identity era → () # | |||||
| Show (ShelleyPParams Identity era) Source # | |||||
Defined in Cardano.Ledger.Shelley.PParams | |||||
| Eq (ShelleyPParams Identity era) Source # | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods (==) ∷ ShelleyPParams Identity era → ShelleyPParams Identity era → Bool # (/=) ∷ ShelleyPParams Identity era → ShelleyPParams Identity era → Bool # | |||||
| Ord (ShelleyPParams Identity era) Source # | |||||
Defined in Cardano.Ledger.Shelley.PParams Methods compare ∷ ShelleyPParams Identity era → ShelleyPParams Identity era → Ordering # (<) ∷ ShelleyPParams Identity era → ShelleyPParams Identity era → Bool # (<=) ∷ ShelleyPParams Identity era → ShelleyPParams Identity era → Bool # (>) ∷ ShelleyPParams Identity era → ShelleyPParams Identity era → Bool # (>=) ∷ ShelleyPParams Identity era → ShelleyPParams Identity era → Bool # max ∷ ShelleyPParams Identity era → ShelleyPParams Identity era → ShelleyPParams Identity era # min ∷ ShelleyPParams Identity era → ShelleyPParams Identity era → ShelleyPParams Identity era # | |||||
| NoThunks (ShelleyPParams Identity era) Source # | |||||
| type Rep Identity | |||||
Defined in Data.Functor.Rep | |||||
| type Rep1 Identity | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity | |||||
| type StM Identity a | |||||
Defined in Control.Monad.Trans.Control | |||||
| newtype MVector s (Identity a) | |||||
Defined in Data.Vector.Unboxed.Base | |||||
| type Rep (Identity a) | Since: base-4.8.0.0 | ||||
Defined in GHC.Internal.Data.Functor.Identity | |||||
| type Index (Identity a) | |||||
Defined in Control.Lens.At | |||||
| type IxValue (Identity a) | |||||
Defined in Control.Lens.At | |||||
| type Unwrapped (Identity a) | |||||
Defined in Control.Lens.Wrapped | |||||
| type Element (Identity a) | |||||
Defined in Data.MonoTraversable | |||||
| newtype Vector (Identity a) | |||||
Defined in Data.Vector.Unboxed.Base | |||||
lift ∷ (MonadTrans t, Monad m) ⇒ m a → t m a #
Lift a computation from the argument monad to the constructed monad.
data PulsingRewUpdate Source #
The state used in the STS rules
Constructors
| Pulsing !RewardSnapShot !Pulser | |
| Complete !RewardUpdate |
Instances
| ToJSON PulsingRewUpdate Source # | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate Methods toJSON ∷ PulsingRewUpdate → Value Source # toEncoding ∷ PulsingRewUpdate → Encoding Source # toJSONList ∷ [PulsingRewUpdate] → Value Source # | |||||
| DecCBOR PulsingRewUpdate Source # | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate | |||||
| EncCBOR PulsingRewUpdate Source # | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate Methods | |||||
| NFData PulsingRewUpdate Source # | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate Methods rnf ∷ PulsingRewUpdate → () # | |||||
| Generic PulsingRewUpdate Source # | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate Associated Types
Methods from ∷ PulsingRewUpdate → Rep PulsingRewUpdate x # to ∷ Rep PulsingRewUpdate x → PulsingRewUpdate # | |||||
| Show PulsingRewUpdate Source # | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate Methods showsPrec ∷ Int → PulsingRewUpdate → ShowS # show ∷ PulsingRewUpdate → String # showList ∷ [PulsingRewUpdate] → ShowS # | |||||
| Eq PulsingRewUpdate Source # | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate Methods | |||||
| NoThunks PulsingRewUpdate Source # | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate | |||||
| type Rep PulsingRewUpdate Source # | |||||
Defined in Cardano.Ledger.Shelley.RewardUpdate type Rep PulsingRewUpdate = D1 ('MetaData "PulsingRewUpdate" "Cardano.Ledger.Shelley.RewardUpdate" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "Pulsing" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RewardSnapShot) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Pulser)) :+: C1 ('MetaCons "Complete" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RewardUpdate))) | |||||
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
startStep ∷ (EraGov era, EraCertState era) ⇒ EpochSize → BlocksMade → EpochState era → Coin → ActiveSlotCoeff → NonZero Word64 → PulsingRewUpdate Source #
pulseStep ∷ PulsingRewUpdate → ShelleyBase (PulsingRewUpdate, RewardEvent) Source #
Run the pulser for a bit. If is has nothing left to do, complete it.
data ShelleyRUPD era Source #
Instances
| (Era era, EraGov era, EraCertState era) ⇒ STS (ShelleyRUPD era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Rupd Associated Types
Methods initialRules ∷ [InitialRule (ShelleyRUPD era)] Source # transitionRules ∷ [TransitionRule (ShelleyRUPD era)] Source # assertions ∷ [Assertion (ShelleyRUPD era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyRUPD era) → String Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyRUPD era), Event (EraRule "RUPD" era) ~ RupdEvent) ⇒ Embed (ShelleyRUPD era) (ShelleyTICK era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Methods wrapFailed ∷ PredicateFailure (ShelleyRUPD era) → PredicateFailure (ShelleyTICK era) Source # wrapEvent ∷ Event (ShelleyRUPD era) → Event (ShelleyTICK era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyRUPD era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |||||||||||||||||||||||||
| type Environment (ShelleyRUPD era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |||||||||||||||||||||||||
| type Event (ShelleyRUPD era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyRUPD era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |||||||||||||||||||||||||
| type Signal (ShelleyRUPD era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |||||||||||||||||||||||||
| type State (ShelleyRUPD era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |||||||||||||||||||||||||
Instances
| NFData RupdEvent Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |||||
| Generic RupdEvent Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Rupd Associated Types
| |||||
| Eq RupdEvent Source # | |||||
| type Rep RupdEvent Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Rupd type Rep RupdEvent = D1 ('MetaData "RupdEvent" "Cardano.Ledger.Shelley.Rules.Rupd" "cardano-ledger-shelley-1.18.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) (Set Reward))))) | |||||
Constructors
| RupdEnv BlocksMade (EpochState era) |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
data ShelleySNAP era Source #
Instances
| (EraTxOut era, EraStake era, EraCertState era) ⇒ STS (ShelleySNAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Snap Associated Types
Methods initialRules ∷ [InitialRule (ShelleySNAP era)] Source # transitionRules ∷ [TransitionRule (ShelleySNAP era)] Source # assertions ∷ [Assertion (ShelleySNAP era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleySNAP era) → String Source # | |||||||||||||||||||||||||
| (EraTxOut era, EraStake era, Event (EraRule "SNAP" era) ~ SnapEvent era, EraCertState era) ⇒ Embed (ShelleySNAP era) (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch Methods wrapFailed ∷ PredicateFailure (ShelleySNAP era) → PredicateFailure (ShelleyEPOCH era) Source # wrapEvent ∷ Event (ShelleySNAP era) → Event (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleySNAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Snap | |||||||||||||||||||||||||
| type Environment (ShelleySNAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Snap | |||||||||||||||||||||||||
| type Event (ShelleySNAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Snap | |||||||||||||||||||||||||
| type PredicateFailure (ShelleySNAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Snap | |||||||||||||||||||||||||
| type Signal (ShelleySNAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Snap | |||||||||||||||||||||||||
| type State (ShelleySNAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Snap | |||||||||||||||||||||||||
newtype SnapEvent era Source #
Constructors
| StakeDistEvent (Map (Credential 'Staking) (Coin, KeyHash 'StakePool)) |
Instances
| NFData (SnapEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Snap | |||||
| Generic (SnapEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Snap Associated Types
| |||||
| 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.18.0.0-inplace" 'True) (C1 ('MetaCons "StakeDistEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (Credential 'Staking) (Coin, KeyHash 'StakePool))))) | |||||
Type of the state which the system transitions between.
Instances
| type State (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type State (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type State (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type State (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type State (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type State (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type State (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type State (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type State (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type State (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type State (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type State (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type State (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type State (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type State (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type State (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type State (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type State (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type State (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type State (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type State (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
Type of the state which the system transitions between.
Instances
| type State (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type State (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type State (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type State (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type State (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type State (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type State (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type State (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type State (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type State (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type State (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type State (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type State (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type State (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type State (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type State (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type State (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type State (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type State (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type State (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type State (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
data ShelleyTICK era Source #
Instances
| (EraGov era, EraCertState era, Embed (EraRule "NEWEPOCH" era) (ShelleyTICK era), Embed (EraRule "RUPD" era) (ShelleyTICK era), State (ShelleyTICK era) ~ NewEpochState era, BaseM (ShelleyTICK era) ~ ShelleyBase, Environment (EraRule "RUPD" era) ~ RupdEnv era, State (EraRule "RUPD" era) ~ StrictMaybe PulsingRewUpdate, Signal (EraRule "RUPD" era) ~ SlotNo, Environment (EraRule "NEWEPOCH" era) ~ (), State (EraRule "NEWEPOCH" era) ~ NewEpochState era, Signal (EraRule "NEWEPOCH" era) ~ EpochNo) ⇒ STS (ShelleyTICK era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Associated Types
Methods initialRules ∷ [InitialRule (ShelleyTICK era)] Source # transitionRules ∷ [TransitionRule (ShelleyTICK era)] Source # assertions ∷ [Assertion (ShelleyTICK era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyTICK era) → String Source # | |||||||||||||||||||||||||
| (STS (ShelleyNEWEPOCH era), Event (EraRule "NEWEPOCH" era) ~ ShelleyNewEpochEvent era) ⇒ Embed (ShelleyNEWEPOCH era) (ShelleyTICK era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Methods wrapFailed ∷ PredicateFailure (ShelleyNEWEPOCH era) → PredicateFailure (ShelleyTICK era) Source # wrapEvent ∷ Event (ShelleyNEWEPOCH era) → Event (ShelleyTICK era) Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyRUPD era), Event (EraRule "RUPD" era) ~ RupdEvent) ⇒ Embed (ShelleyRUPD era) (ShelleyTICK era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Methods wrapFailed ∷ PredicateFailure (ShelleyRUPD era) → PredicateFailure (ShelleyTICK era) Source # wrapEvent ∷ Event (ShelleyRUPD era) → Event (ShelleyTICK era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyTICK era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick | |||||||||||||||||||||||||
| type Environment (ShelleyTICK era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick | |||||||||||||||||||||||||
| type Event (ShelleyTICK era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyTICK era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick | |||||||||||||||||||||||||
| type Signal (ShelleyTICK era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick | |||||||||||||||||||||||||
| type State (ShelleyTICK era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick | |||||||||||||||||||||||||
data ShelleyTICKF era Source #
Instances
| (EraGov era, EraCertState era, GovState era ~ ShelleyGovState era, State (EraRule "PPUP" era) ~ ShelleyGovState era, Signal (EraRule "UPEC" era) ~ (), State (EraRule "UPEC" era) ~ UpecState era, Environment (EraRule "UPEC" era) ~ LedgerState era, Embed (EraRule "UPEC" era) (ShelleyTICKF era)) ⇒ STS (ShelleyTICKF era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Associated Types
Methods initialRules ∷ [InitialRule (ShelleyTICKF era)] Source # transitionRules ∷ [TransitionRule (ShelleyTICKF era)] Source # assertions ∷ [Assertion (ShelleyTICKF era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyTICKF era) → String Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyUPEC era), Event (EraRule "UPEC" era) ~ Void) ⇒ Embed (ShelleyUPEC era) (ShelleyTICKF era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Methods wrapFailed ∷ PredicateFailure (ShelleyUPEC era) → PredicateFailure (ShelleyTICKF era) Source # wrapEvent ∷ Event (ShelleyUPEC era) → Event (ShelleyTICKF era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyTICKF era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick | |||||||||||||||||||||||||
| type Environment (ShelleyTICKF era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick | |||||||||||||||||||||||||
| type Event (ShelleyTICKF era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyTICKF era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick | |||||||||||||||||||||||||
| type Signal (ShelleyTICKF era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick | |||||||||||||||||||||||||
| type State (ShelleyTICKF era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick | |||||||||||||||||||||||||
data ShelleyTickEvent era Source #
Constructors
| TickNewEpochEvent (Event (EraRule "NEWEPOCH" era)) | |
| TickRupdEvent (Event (EraRule "RUPD" era)) |
Instances
| (NFData (Event (EraRule "NEWEPOCH" era)), NFData (Event (EraRule "RUPD" era))) ⇒ NFData (ShelleyTickEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Methods rnf ∷ ShelleyTickEvent era → () # | |||||
| Generic (ShelleyTickEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Associated Types
Methods from ∷ ShelleyTickEvent era → Rep (ShelleyTickEvent era) x # to ∷ Rep (ShelleyTickEvent era) x → ShelleyTickEvent era # | |||||
| (Eq (Event (EraRule "NEWEPOCH" era)), Eq (Event (EraRule "RUPD" era))) ⇒ Eq (ShelleyTickEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Methods (==) ∷ ShelleyTickEvent era → ShelleyTickEvent era → Bool # (/=) ∷ ShelleyTickEvent era → ShelleyTickEvent era → Bool # | |||||
| type Rep (ShelleyTickEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Tick type Rep (ShelleyTickEvent era) = D1 ('MetaData "ShelleyTickEvent" "Cardano.Ledger.Shelley.Rules.Tick" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "TickNewEpochEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "NEWEPOCH" era)))) :+: C1 ('MetaCons "TickRupdEvent" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Event (EraRule "RUPD" era))))) | |||||
adoptGenesisDelegs ∷ EraCertState era ⇒ EpochState era → SlotNo → EpochState era Source #
validatingTickTransition ∷ ∀ tick era. (EraGov era, EraCertState 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 ∷ (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, EraCertState 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
| (EraGov era, Default (PParams era), GovState era ~ ShelleyGovState era, AtMostEra "Babbage" era) ⇒ STS (ShelleyUPEC era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Upec Associated Types
Methods initialRules ∷ [InitialRule (ShelleyUPEC era)] Source # transitionRules ∷ [TransitionRule (ShelleyUPEC era)] Source # assertions ∷ [Assertion (ShelleyUPEC era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyUPEC era) → String Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyNEWPP era)) ⇒ Embed (ShelleyNEWPP era) (ShelleyUPEC era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Upec Methods wrapFailed ∷ PredicateFailure (ShelleyNEWPP era) → PredicateFailure (ShelleyUPEC era) Source # wrapEvent ∷ Event (ShelleyNEWPP era) → Event (ShelleyUPEC era) Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyUPEC era), Event (EraRule "UPEC" era) ~ Void) ⇒ Embed (ShelleyUPEC era) (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch Methods wrapFailed ∷ PredicateFailure (ShelleyUPEC era) → PredicateFailure (ShelleyEPOCH era) Source # wrapEvent ∷ Event (ShelleyUPEC era) → Event (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyUPEC era), Event (EraRule "UPEC" era) ~ Void) ⇒ Embed (ShelleyUPEC era) (ShelleyTICKF era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Tick Methods wrapFailed ∷ PredicateFailure (ShelleyUPEC era) → PredicateFailure (ShelleyTICKF era) Source # wrapEvent ∷ Event (ShelleyUPEC era) → Event (ShelleyTICKF era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyUPEC era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Upec | |||||||||||||||||||||||||
| type Environment (ShelleyUPEC era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Upec | |||||||||||||||||||||||||
| type Event (ShelleyUPEC era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Upec | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyUPEC era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Upec | |||||||||||||||||||||||||
| type Signal (ShelleyUPEC era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Upec | |||||||||||||||||||||||||
| type State (ShelleyUPEC era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Upec | |||||||||||||||||||||||||
Constructors
| UpecState | |
Fields
| |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
data ShelleyMIR era Source #
Instances
| (Default (EpochState era), EraGov era, EraCertState era) ⇒ STS (ShelleyMIR era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Mir Associated Types
Methods initialRules ∷ [InitialRule (ShelleyMIR era)] Source # transitionRules ∷ [TransitionRule (ShelleyMIR era)] Source # assertions ∷ [Assertion (ShelleyMIR era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyMIR era) → String Source # | |||||||||||||||||||||||||
| (EraGov era, EraCertState era, Default (EpochState era), Event (EraRule "MIR" era) ~ ShelleyMirEvent era) ⇒ Embed (ShelleyMIR era) (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch Methods wrapFailed ∷ PredicateFailure (ShelleyMIR era) → PredicateFailure (ShelleyNEWEPOCH era) Source # wrapEvent ∷ Event (ShelleyMIR era) → Event (ShelleyNEWEPOCH era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyMIR era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Mir | |||||||||||||||||||||||||
| type Environment (ShelleyMIR era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Mir | |||||||||||||||||||||||||
| type Event (ShelleyMIR era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Mir | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyMIR era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Mir | |||||||||||||||||||||||||
| type Signal (ShelleyMIR era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Mir | |||||||||||||||||||||||||
| type State (ShelleyMIR era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Mir | |||||||||||||||||||||||||
data ShelleyMirEvent era Source #
Constructors
| MirTransfer InstantaneousRewards | |
| NoMirTransfer InstantaneousRewards 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
| NFData (ShelleyMirEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Mir Methods rnf ∷ ShelleyMirEvent era → () # | |||||
| Generic (ShelleyMirEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Mir Associated Types
Methods from ∷ ShelleyMirEvent era → Rep (ShelleyMirEvent era) x # to ∷ Rep (ShelleyMirEvent era) x → ShelleyMirEvent era # | |||||
| Eq (ShelleyMirEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Mir Methods (==) ∷ ShelleyMirEvent era → ShelleyMirEvent era → Bool # (/=) ∷ ShelleyMirEvent era → ShelleyMirEvent era → Bool # | |||||
| type Rep (ShelleyMirEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.Mir type Rep (ShelleyMirEvent era) = D1 ('MetaData "ShelleyMirEvent" "Cardano.Ledger.Shelley.Rules.Mir" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "MirTransfer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InstantaneousRewards)) :+: C1 ('MetaCons "NoMirTransfer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 InstantaneousRewards) :*: (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Coin)))) | |||||
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
data ShelleyNEWPP era Source #
Instances
| (EraGov era, GovState era ~ ShelleyGovState era, AtMostEra "Babbage" era) ⇒ STS (ShelleyNEWPP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Newpp Associated Types
Methods initialRules ∷ [InitialRule (ShelleyNEWPP era)] Source # transitionRules ∷ [TransitionRule (ShelleyNEWPP era)] Source # assertions ∷ [Assertion (ShelleyNEWPP era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyNEWPP era) → String Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyNEWPP era)) ⇒ Embed (ShelleyNEWPP era) (ShelleyUPEC era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Upec Methods wrapFailed ∷ PredicateFailure (ShelleyNEWPP era) → PredicateFailure (ShelleyUPEC era) Source # wrapEvent ∷ Event (ShelleyNEWPP era) → Event (ShelleyUPEC era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyNEWPP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |||||||||||||||||||||||||
| type Environment (ShelleyNEWPP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |||||||||||||||||||||||||
| type Event (ShelleyNEWPP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyNEWPP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |||||||||||||||||||||||||
| type Signal (ShelleyNEWPP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |||||||||||||||||||||||||
| type State (ShelleyNEWPP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |||||||||||||||||||||||||
data ShelleyNewppState era Source #
Constructors
| NewppState (PParams era) (ShelleyGovState era) |
Instances
| EraPParams era ⇒ Default (ShelleyNewppState era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp Methods def ∷ ShelleyNewppState era Source # | |
Constructors
| NewppEnv | |
Fields
| |
data ShelleyPoolreapEvent era Source #
Constructors
| RetiredPools | |
Fields
| |
Instances
| NFData (ShelleyPoolreapEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap Methods rnf ∷ ShelleyPoolreapEvent era → () # | |||||
| Generic (ShelleyPoolreapEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap Associated Types
Methods from ∷ ShelleyPoolreapEvent era → Rep (ShelleyPoolreapEvent era) x # to ∷ Rep (ShelleyPoolreapEvent era) x → ShelleyPoolreapEvent era # | |||||
| Eq (ShelleyPoolreapEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap Methods (==) ∷ ShelleyPoolreapEvent era → ShelleyPoolreapEvent era → Bool # (/=) ∷ ShelleyPoolreapEvent era → ShelleyPoolreapEvent era → Bool # | |||||
| type Rep (ShelleyPoolreapEvent era) Source # | |||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap type Rep (ShelleyPoolreapEvent era) = D1 ('MetaData "ShelleyPoolreapEvent" "Cardano.Ledger.Shelley.Rules.PoolReap" "cardano-ledger-shelley-1.18.0.0-inplace" 'False) (C1 ('MetaCons "RetiredPools" 'PrefixI 'True) (S1 ('MetaSel ('Just "refundPools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (Credential 'Staking) (Map (KeyHash 'StakePool) (CompactForm Coin)))) :*: (S1 ('MetaSel ('Just "unclaimedPools") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (Credential 'Staking) (Map (KeyHash 'StakePool) (CompactForm Coin)))) :*: S1 ('MetaSel ('Just "epochNo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 EpochNo)))) | |||||
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
type family PredicateFailure a Source #
Descriptive type for the possible failures which might cause a transition to fail.
As a convention, PredicateFailures 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 PredicateFailures 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 PredicateFailure (ShelleyBBODY era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Bbody | |
| type PredicateFailure (ShelleyDELEG era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Deleg | |
| type PredicateFailure (ShelleyDELEGS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delegs | |
| type PredicateFailure (ShelleyDELPL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Delpl | |
| type PredicateFailure (ShelleyEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Epoch | |
| type PredicateFailure (ShelleyLEDGER era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledger | |
| type PredicateFailure (ShelleyLEDGERS era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ledgers | |
| type PredicateFailure (ShelleyMIR era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Mir | |
| type PredicateFailure (ShelleyNEWEPOCH era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.NewEpoch | |
| type PredicateFailure (ShelleyNEWPP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Newpp | |
| type PredicateFailure (ShelleyPOOL era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Pool | |
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |
| type PredicateFailure (ShelleyPPUP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Ppup | |
| type PredicateFailure (ShelleyRUPD era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Rupd | |
| type PredicateFailure (ShelleySNAP era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Snap | |
| type PredicateFailure (ShelleyTICK era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyTICKF era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Tick | |
| type PredicateFailure (ShelleyUPEC era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Upec | |
| type PredicateFailure (ShelleyUTXO era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxo | |
| type PredicateFailure (ShelleyUTXOW era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.Utxow | |
| type PredicateFailure (STUB e st si f m) | |
Defined in Control.State.Transition.Extended | |
data ShelleyPOOLREAP era Source #
Instances
| (Default (ShelleyPoolreapState era), EraPParams era, EraGov era, EraCertState era) ⇒ STS (ShelleyPOOLREAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap Associated Types
Methods initialRules ∷ [InitialRule (ShelleyPOOLREAP era)] Source # transitionRules ∷ [TransitionRule (ShelleyPOOLREAP era)] Source # assertions ∷ [Assertion (ShelleyPOOLREAP era)] Source # renderAssertionViolation ∷ AssertionViolation (ShelleyPOOLREAP era) → String Source # | |||||||||||||||||||||||||
| (Era era, STS (ShelleyPOOLREAP era), Event (EraRule "POOLREAP" era) ~ ShelleyPoolreapEvent era) ⇒ Embed (ShelleyPOOLREAP era) (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.Epoch Methods wrapFailed ∷ PredicateFailure (ShelleyPOOLREAP era) → PredicateFailure (ShelleyEPOCH era) Source # wrapEvent ∷ Event (ShelleyPOOLREAP era) → Event (ShelleyEPOCH era) Source # | |||||||||||||||||||||||||
| type BaseM (ShelleyPOOLREAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |||||||||||||||||||||||||
| type Environment (ShelleyPOOLREAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |||||||||||||||||||||||||
| type Event (ShelleyPOOLREAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |||||||||||||||||||||||||
| type PredicateFailure (ShelleyPOOLREAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |||||||||||||||||||||||||
| type Signal (ShelleyPOOLREAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |||||||||||||||||||||||||
| type State (ShelleyPOOLREAP era) Source # | |||||||||||||||||||||||||
Defined in Cardano.Ledger.Shelley.Rules.PoolReap | |||||||||||||||||||||||||
data ShelleyPoolreapState era Source #
Constructors
| PoolreapState | |
Fields
| |
Instances
| (Default (UTxOState era), Default (CertState era)) ⇒ Default (ShelleyPoolreapState era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap Methods def ∷ ShelleyPoolreapState era Source # | |
| (Show (UTxOState era), Show (CertState era)) ⇒ Show (ShelleyPoolreapState era) Source # | |
Defined in Cardano.Ledger.Shelley.Rules.PoolReap Methods showsPrec ∷ Int → ShelleyPoolreapState era → ShowS # show ∷ ShelleyPoolreapState era → String # showList ∷ [ShelleyPoolreapState era] → ShowS # | |
prCertStateL ∷ ∀ era f. Functor f ⇒ (CertState era → f (CertState era)) → ShelleyPoolreapState era → f (ShelleyPoolreapState era) Source #
prChainAccountStateL ∷ ∀ era f. Functor f ⇒ (ChainAccountState → f ChainAccountState) → ShelleyPoolreapState era → f (ShelleyPoolreapState era) Source #
prUTxOStateL ∷ ∀ era f. Functor f ⇒ (UTxOState era → f (UTxOState era)) → ShelleyPoolreapState era → f (ShelleyPoolreapState era) Source #