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