Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module implements the operation rules for treating UTxO transactions (
Tx
)
as state transformations on a ledger state (
LedgerState
),
as specified in
A Simplified Formal Specification of a UTxO Ledger
.
Synopsis
- data AccountState = AccountState { }
- data DPState crypto = DPState { }
-
data
DState
crypto =
DState
{
- _unified :: !( UnifiedMap crypto)
- _fGenDelegs :: !( Map ( FutureGenDeleg crypto) ( GenDelegPair crypto))
- _genDelegs :: !( GenDelegs crypto)
- _irwd :: !( InstantaneousRewards crypto)
- emptyDState :: DState crypto
- rewards :: DState crypto -> ViewMap crypto ( Credential ' Staking crypto) Coin
- delegations :: DState crypto -> ViewMap crypto ( Credential ' Staking crypto) ( KeyHash ' StakePool crypto)
- ptrsMap :: DState crypto -> Map Ptr ( Credential ' Staking crypto)
-
data
EpochState
era =
EpochState
{
- esAccountState :: ! AccountState
- esSnapshots :: !( SnapShots ( Crypto era))
- esLState :: !( LedgerState era)
- esPrevPp :: !( PParams era)
- esPp :: !( PParams era)
- esNonMyopic :: !( NonMyopic ( Crypto era))
- data UpecState era = UpecState { }
-
data
PulsingRewUpdate
crypto
- = Pulsing !( RewardSnapShot crypto) !( Pulser crypto)
- | Complete !( RewardUpdate crypto)
-
data
FutureGenDeleg
crypto =
FutureGenDeleg
{
- fGenDelegSlot :: ! SlotNo
- fGenDelegGenKeyHash :: !( KeyHash ' Genesis crypto)
-
data
InstantaneousRewards
crypto =
InstantaneousRewards
{
- iRReserves :: !( Map ( Credential ' Staking crypto) Coin )
- iRTreasury :: !( Map ( Credential ' Staking crypto) Coin )
- deltaReserves :: ! DeltaCoin
- deltaTreasury :: ! DeltaCoin
- type KeyPairs crypto = [( KeyPair ' Payment crypto, KeyPair ' Staking crypto)]
-
data
LedgerState
era =
LedgerState
{
- lsUTxOState :: !( UTxOState era)
- lsDPState :: !( DPState ( Crypto era))
-
data
PPUPState
era =
PPUPState
{
- proposals :: !( ProposedPPUpdates era)
- futureProposals :: !( ProposedPPUpdates era)
- data PState crypto = PState { }
- type RewardAccounts crypto = Map ( Credential ' Staking crypto) Coin
- data RewardUpdate crypto = RewardUpdate { }
-
data
RewardSnapShot
crypto =
RewardSnapShot
{
- rewFees :: ! Coin
- rewprotocolVersion :: ! ProtVer
- rewNonMyopic :: !( NonMyopic crypto)
- rewDeltaR1 :: ! Coin
- rewR :: ! Coin
- rewDeltaT1 :: ! Coin
- rewLikelihoods :: !( Map ( KeyHash ' StakePool crypto) Likelihood )
- rewLeaders :: !( Map ( Credential ' Staking crypto) ( Set ( Reward crypto)))
-
data
UTxOState
era =
UTxOState
{
- _utxo :: !( UTxO era)
- _deposited :: ! Coin
- _fees :: ! Coin
- _ppups :: !( State ( EraRule "PPUP" era))
- _stakeDistro :: !( IncrementalStake ( Crypto era))
- smartUTxOState :: Era era => UTxO era -> Coin -> Coin -> State ( EraRule "PPUP" era) -> UTxOState era
- data IncrementalStake crypto = IStake { }
- depositPoolChange :: HasField "certs" ( TxBody era) ( StrictSeq ( DCert ( Crypto era))) => LedgerState era -> PParams era -> TxBody era -> Coin
- emptyRewardUpdate :: RewardUpdate crypto
- pvCanFollow :: ProtVer -> StrictMaybe ProtVer -> Bool
- reapRewards :: UnifiedMap crypto -> RewardAccounts crypto -> UnifiedMap crypto
- availableAfterMIR :: MIRPot -> AccountState -> InstantaneousRewards crypto -> Coin
- genesisState :: Default ( State ( EraRule "PPUP" era)) => Map ( KeyHash ' Genesis ( Crypto era)) ( GenDelegPair ( Crypto era)) -> UTxO era -> LedgerState era
-
newtype
WitHashes
crypto =
WitHashes
{
- unWitHashes :: Set ( KeyHash ' Witness crypto)
- nullWitHashes :: WitHashes crypto -> Bool
- diffWitHashes :: WitHashes crypto -> WitHashes crypto -> WitHashes crypto
- minfee :: ( HasField "_minfeeA" pp Natural , HasField "_minfeeB" pp Natural , HasField "txsize" tx Integer ) => pp -> tx -> Coin
- txsizeBound :: forall era out tx. ( HasField "outputs" ( TxBody era) ( StrictSeq out), HasField "inputs" ( TxBody era) ( Set ( TxIn ( Crypto era))), HasField "body" tx ( TxBody era), HasField "txsize" tx Integer ) => Proxy era -> tx -> Integer
- produced :: forall era pp. ( Era era, HasField "certs" ( TxBody era) ( StrictSeq ( DCert ( Crypto era))), HasField "_keyDeposit" pp Coin , HasField "_poolDeposit" pp Coin ) => pp -> ( KeyHash ' StakePool ( Crypto era) -> Bool ) -> TxBody era -> Value era
- consumed :: forall era pp. ( Era era, HasField "certs" ( TxBody era) ( StrictSeq ( DCert ( Crypto era))), HasField "inputs" ( TxBody era) ( Set ( TxIn ( Crypto era))), HasField "wdrls" ( TxBody era) ( Wdrl ( Crypto era)), HasField "_keyDeposit" pp Coin ) => pp -> UTxO era -> TxBody era -> Value era
- witsFromTxWitnesses :: ( Era era, HasField "addrWits" tx ( Set ( WitVKey ' Witness ( Crypto era))), HasField "bootWits" tx ( Set ( BootstrapWitness ( Crypto era)))) => tx -> WitHashes ( Crypto era)
- propWits :: Maybe ( Update era) -> GenDelegs ( Crypto era) -> Set ( KeyHash ' Witness ( Crypto era))
- keyRefunds :: ( HasField "certs" txb ( StrictSeq ( DCert crypto)), HasField "_keyDeposit" pp Coin ) => pp -> txb -> Coin
- incrementalStakeDistr :: forall crypto. IncrementalStake crypto -> DState crypto -> PState crypto -> SnapShot crypto
- updateStakeDistribution :: Era era => IncrementalStake ( Crypto era) -> UTxO era -> UTxO era -> IncrementalStake ( Crypto era)
- applyRUpd :: HasField "_protocolVersion" ( PParams era) ProtVer => RewardUpdate ( Crypto era) -> EpochState era -> EpochState era
- applyRUpd' :: HasField "_protocolVersion" ( PParams era) ProtVer => RewardUpdate ( Crypto era) -> EpochState era -> ( EpochState era, Map ( Credential ' Staking ( Crypto era)) ( Set ( Reward ( Crypto era))), Map ( Credential ' Staking ( Crypto era)) ( Set ( Reward ( Crypto era))), Set ( Credential ' Staking ( Crypto era)))
- filterAllRewards :: HasField "_protocolVersion" ( PParams era) ProtVer => Map ( Credential ' Staking ( Crypto era)) ( Set ( Reward ( Crypto era))) -> EpochState era -> ( Map ( Credential ' Staking ( Crypto era)) ( Set ( Reward ( Crypto era))), Map ( Credential ' Staking ( Crypto era)) ( Set ( Reward ( Crypto era))), Set ( Credential ' Staking ( Crypto era)), Coin )
- createRUpd :: forall era. UsesPP era => EpochSize -> BlocksMade ( Crypto era) -> EpochState era -> Coin -> ActiveSlotCoeff -> Word64 -> ProvM ( RewardProvenance ( Crypto era)) ShelleyBase ( RewardUpdate ( Crypto era))
- completeRupd :: PulsingRewUpdate crypto -> ProvM ( RewardProvenance crypto) ShelleyBase ( RewardUpdate crypto, RewardEvent crypto)
- startStep :: forall era. UsesPP era => EpochSize -> BlocksMade ( Crypto era) -> EpochState era -> Coin -> ActiveSlotCoeff -> Word64 -> ( PulsingRewUpdate ( Crypto era), RewardProvenance ( Crypto era))
- pulseStep :: PulsingRewUpdate crypto -> ShelleyBase ( PulsingRewUpdate crypto, RewardEvent crypto)
- completeStep :: PulsingRewUpdate crypto -> ShelleyBase ( PulsingRewUpdate crypto, RewardEvent crypto)
- data NewEpochState era = NewEpochState ! EpochNo !( BlocksMade ( Crypto era)) !( BlocksMade ( Crypto era)) !( EpochState era) !( StrictMaybe ( PulsingRewUpdate ( Crypto era))) !( PoolDistr ( Crypto era)) !( StashedAVVMAddresses era)
- type family StashedAVVMAddresses era where ...
- stashedAVVMAddresses :: NewEpochState era -> StashedAVVMAddresses era
- getGKeys :: NewEpochState era -> Set ( KeyHash ' Genesis ( Crypto era))
- updateNES :: NewEpochState era -> BlocksMade ( Crypto era) -> LedgerState era -> NewEpochState era
- circulation :: EpochState era -> Coin -> Coin
- decayFactor :: Float
- returnRedeemAddrsToReserves :: forall era. Era era => EpochState era -> EpochState era
- updateNonMyopic :: NonMyopic crypto -> Coin -> Map ( KeyHash ' StakePool crypto) Likelihood -> NonMyopic crypto
Documentation
data AccountState Source #
Instances
The state associated with the current stake delegation.
Instances
State of staking pool delegations and rewards
DState | |
|
Instances
emptyDState :: DState crypto Source #
delegations :: DState crypto -> ViewMap crypto ( Credential ' Staking crypto) ( KeyHash ' StakePool crypto) Source #
ptrsMap :: DState crypto -> Map Ptr ( Credential ' Staking crypto) Source #
get the actual ptrs map, we don't need a view
data EpochState era Source #
EpochState | |
|
Instances
data PulsingRewUpdate crypto Source #
The state used in the STS rules
Pulsing !( RewardSnapShot crypto) !( Pulser crypto) | |
Complete !( RewardUpdate crypto) |
Instances
data FutureGenDeleg crypto Source #
FutureGenDeleg | |
|
Instances
data InstantaneousRewards crypto Source #
InstantaneousRewards captures the pending changes to the ledger state caused by MIR certificates. It consists of two mappings, the rewards which will be paid out from the reserves and the rewards which will be paid out from the treasury. It also consists of two coin values which represent the transfer of coins from one pot to the other pot. NOTE that the following property should always hold: deltaReserves + deltaTreasury = 0
InstantaneousRewards | |
|
Instances
type KeyPairs crypto = [( KeyPair ' Payment crypto, KeyPair ' Staking crypto)] Source #
Representation of a list of pairs of key pairs, e.g., pay and stake keys
data LedgerState era Source #
The state associated with a
Ledger
.
LedgerState | |
|
Instances
PPUPState | |
|
Instances
Current state of staking pools and their certificate counters.
PState | |
|
Instances
type RewardAccounts crypto = Map ( Credential ' Staking crypto) Coin Source #
data RewardUpdate crypto Source #
The ultiate goal of a reward update computation. Aggregating rewards for each staking credential.
Instances
data RewardSnapShot crypto Source #
To complete the reward update, we need a snap shot of the EpochState particular to this computation
RewardSnapShot | |
|
Instances
There is a serious invariant that we must maintain in the UTxOState. Given (UTxOState utxo _ _ _ istake) it must be the case that istake == (updateStakeDistribution (UTxO Map.empty) (UTxO Map.empty) utxo) Of course computing the RHS of the above equality can be very expensive, so we only use this route in the testing function smartUTxO. But we are very carefull, wherever we update the UTxO, we carefully make INCREMENTAL changes to istake to maintain this invariant. This happens in the UTxO rule.
UTxOState | |
|
Instances
smartUTxOState :: Era era => UTxO era -> Coin -> Coin -> State ( EraRule "PPUP" era) -> UTxOState era Source #
A valid (or self-consistent) UTxOState{_utxo, _deposited, _fees, _ppups, _stakeDistro} maintains an invariant between the _utxo and _stakeDistro fields. the _stakeDistro field is the aggregation of Coin over the StakeReferences in the UTxO. It can be computed by a pure function from the _utxo field. In some situations, mostly unit or example tests, or when initializing a small UTxO, we want to create a UTxOState that computes the _stakeDistro from the _utxo. This is aways safe to do, but if the _utxo field is big, this can be very expensive, which defeats the purpose of memoizing the _stakeDistro field. So use of this function should be restricted to tests and initializations, where the invariant should be maintained.
data IncrementalStake crypto Source #
Incremental Stake, Stake along with possible missed coins from danging Ptrs.
Transactions can use Ptrs to refer to a stake credential in a TxOut. The Ptr
does not have to point to anything until the epoch boundary, when we compute
rewards and aggregate staking information for ranking. This is unusual but legal.
In a non incremental system, we use whatever
legal
Ptrs exist at the epoch
boundary. Here we are computing things incrementally, so we need to remember Ptrs
that might point to something by the time the epoch boundary is reached. When
the epoch boundary is reached we
resolve
these pointers, to see if any have
become non-dangling since the time they were first used in the incremental computation.
Instances
depositPoolChange :: HasField "certs" ( TxBody era) ( StrictSeq ( DCert ( Crypto era))) => LedgerState era -> PParams era -> TxBody era -> Coin Source #
Calculate the change to the deposit pool for a given transaction.
emptyRewardUpdate :: RewardUpdate crypto Source #
pvCanFollow :: ProtVer -> StrictMaybe ProtVer -> Bool Source #
reapRewards :: UnifiedMap crypto -> RewardAccounts crypto -> UnifiedMap crypto Source #
availableAfterMIR :: MIRPot -> AccountState -> InstantaneousRewards crypto -> Coin Source #
This function returns the coin balance of a given pot, either the reserves or the treasury, after the instantaneous rewards and pot transfers are accounted for.
Genesis State
genesisState :: Default ( State ( EraRule "PPUP" era)) => Map ( KeyHash ' Genesis ( Crypto era)) ( GenDelegPair ( Crypto era)) -> UTxO era -> LedgerState era Source #
Creates the ledger state for an empty ledger which contains the specified transaction outputs.
Validation
newtype WitHashes crypto Source #
WitHashes | |
|
Instances
Eq ( WitHashes crypto) Source # | |
Show ( WitHashes crypto) Source # | |
Generic ( WitHashes crypto) Source # | |
NoThunks ( WitHashes crypto) Source # | |
type Rep ( WitHashes crypto) Source # | |
Defined in Cardano.Ledger.Shelley.LedgerState
type
Rep
(
WitHashes
crypto) =
D1
('
MetaData
"WitHashes" "Cardano.Ledger.Shelley.LedgerState" "cardano-ledger-shelley-0.1.0.0-4LNBTpyKcsy6EW18a3tTt2" '
True
) (
C1
('
MetaCons
"WitHashes" '
PrefixI
'
True
) (
S1
('
MetaSel
('
Just
"unWitHashes") '
NoSourceUnpackedness
'
NoSourceStrictness
'
DecidedLazy
) (
Rec0
(
Set
(
KeyHash
'
Witness
crypto)))))
|
nullWitHashes :: WitHashes crypto -> Bool Source #
Check if a set of witness hashes is empty.
diffWitHashes :: WitHashes crypto -> WitHashes crypto -> WitHashes crypto Source #
Extract the difference between two sets of witness hashes.
minfee :: ( HasField "_minfeeA" pp Natural , HasField "_minfeeB" pp Natural , HasField "txsize" tx Integer ) => pp -> tx -> Coin Source #
Minimum fee calculation
txsizeBound :: forall era out tx. ( HasField "outputs" ( TxBody era) ( StrictSeq out), HasField "inputs" ( TxBody era) ( Set ( TxIn ( Crypto era))), HasField "body" tx ( TxBody era), HasField "txsize" tx Integer ) => Proxy era -> tx -> Integer Source #
Convenience Function to bound the txsize function. | It can be helpful for coin selection.
produced :: forall era pp. ( Era era, HasField "certs" ( TxBody era) ( StrictSeq ( DCert ( Crypto era))), HasField "_keyDeposit" pp Coin , HasField "_poolDeposit" pp Coin ) => pp -> ( KeyHash ' StakePool ( Crypto era) -> Bool ) -> TxBody era -> Value era Source #
Compute the lovelace which are created by the transaction
consumed :: forall era pp. ( Era era, HasField "certs" ( TxBody era) ( StrictSeq ( DCert ( Crypto era))), HasField "inputs" ( TxBody era) ( Set ( TxIn ( Crypto era))), HasField "wdrls" ( TxBody era) ( Wdrl ( Crypto era)), HasField "_keyDeposit" pp Coin ) => pp -> UTxO era -> TxBody era -> Value era Source #
Compute the lovelace which are destroyed by the transaction
witsFromTxWitnesses :: ( Era era, HasField "addrWits" tx ( Set ( WitVKey ' Witness ( Crypto era))), HasField "bootWits" tx ( Set ( BootstrapWitness ( Crypto era)))) => tx -> WitHashes ( Crypto era) Source #
Extract the witness hashes from the Transaction.
propWits :: Maybe ( Update era) -> GenDelegs ( Crypto era) -> Set ( KeyHash ' Witness ( Crypto era)) Source #
Calculate the set of hash keys of the required witnesses for update proposals.
DelegationState
keyRefunds :: ( HasField "certs" txb ( StrictSeq ( DCert crypto)), HasField "_keyDeposit" pp Coin ) => pp -> txb -> Coin Source #
Compute the key deregistration refunds in a transaction
Epoch boundary
incrementalStakeDistr :: forall crypto. IncrementalStake crypto -> DState crypto -> PState crypto -> SnapShot crypto Source #
Compute the current state distribution by using the IncrementalStake,
This computes the stake distribution using IncrementalStake (which is an aggregate of the current UTxO) and UnifiedMap (which tracks Coin, Delegations, and Ptrs simultaneously). Note that logically: 1) IncrementalStake = (credStake, ptrStake) 2) UnifiedMap = (rewards, activeDelegs, ptrmap :: Map ptr cred)
Using this scheme the logic can do 3 things in one go, without touching the UTxO. 1) Resolve Pointers 2) Throw away things not actively delegated 3) Add up the coin
The Stake distribution function (Map cred coin) (the first component of a SnapShot) is defined by this SetAlgebra expression: (dom activeDelegs) ◁ (aggregate+ (credStake ∪ ptrStake ∪ rewards))
We can apply meaning preserving operations to get equivalent expressions
(dom activeDelegs) ◁ (aggregate+ (credStake ∪ ptrStake ∪ rewards)) aggregate+ (dom activeDelegs ◁ (credStake ∪ ptrStake ∪ rewards)) aggregate+ ((dom activeDelegs ◁ credStake) ∪ (dom activeDelegs ◁ ptrStake) ∪ (dom activeDelegs ◁ rewards))
We will compute this in several steps
step1 = (dom activeDelegs ◁ credStake) ∪ (dom activeDelegs ◁ ptrStake)
step2 = aggregate (dom activeDelegs ◁ rewards) step1
This function has a non-incremental analog,
stakeDistr
, mosty used in tests, which does use the UTxO.
updateStakeDistribution :: Era era => IncrementalStake ( Crypto era) -> UTxO era -> UTxO era -> IncrementalStake ( Crypto era) Source #
Incrementally add the inserts
utxoAdd
and the deletes
utxoDel
to the IncrementalStake.
applyRUpd :: HasField "_protocolVersion" ( PParams era) ProtVer => RewardUpdate ( Crypto era) -> EpochState era -> EpochState era Source #
Apply a reward update
applyRUpd' :: HasField "_protocolVersion" ( PParams era) ProtVer => RewardUpdate ( Crypto era) -> EpochState era -> ( EpochState era, Map ( Credential ' Staking ( Crypto era)) ( Set ( Reward ( Crypto era))), Map ( Credential ' Staking ( Crypto era)) ( Set ( Reward ( Crypto era))), Set ( Credential ' Staking ( Crypto era))) Source #
filterAllRewards :: HasField "_protocolVersion" ( PParams era) ProtVer => Map ( Credential ' Staking ( Crypto era)) ( Set ( Reward ( Crypto era))) -> EpochState era -> ( Map ( Credential ' Staking ( Crypto era)) ( Set ( Reward ( Crypto era))), Map ( Credential ' Staking ( Crypto era)) ( Set ( Reward ( Crypto era))), Set ( Credential ' Staking ( Crypto era)), Coin ) Source #
createRUpd :: forall era. UsesPP era => EpochSize -> BlocksMade ( Crypto era) -> EpochState era -> Coin -> ActiveSlotCoeff -> Word64 -> ProvM ( RewardProvenance ( Crypto era)) ShelleyBase ( RewardUpdate ( Crypto era)) Source #
To create a reward update, run all 3 phases This function is not used in the rules, so it ignores RewardEvents
completeRupd :: PulsingRewUpdate crypto -> ProvM ( RewardProvenance crypto) ShelleyBase ( RewardUpdate crypto, RewardEvent crypto) Source #
Phase 3 of reward update has several parts a) completeM the pulser (in case there are still computions to run) b) Combine the pulser provenance with the RewardProvenance c) Construct the final RewardUpdate d) Add the leader rewards to both the events and the computed Rewards
startStep :: forall era. UsesPP era => EpochSize -> BlocksMade ( Crypto era) -> EpochState era -> Coin -> ActiveSlotCoeff -> Word64 -> ( PulsingRewUpdate ( Crypto era), RewardProvenance ( Crypto era)) Source #
Assemble the components for, and then create, a Pulser.
pulseStep :: PulsingRewUpdate crypto -> ShelleyBase ( PulsingRewUpdate crypto, RewardEvent crypto) Source #
Run the pulser for a bit. If is has nothing left to do, complete it.
completeStep :: PulsingRewUpdate crypto -> ShelleyBase ( PulsingRewUpdate crypto, RewardEvent crypto) Source #
data NewEpochState era Source #
New Epoch state and environment
NewEpochState ! EpochNo !( BlocksMade ( Crypto era)) !( BlocksMade ( Crypto era)) !( EpochState era) !( StrictMaybe ( PulsingRewUpdate ( Crypto era))) !( PoolDistr ( Crypto era)) !( StashedAVVMAddresses era) |
Instances
type family StashedAVVMAddresses era where ... Source #
StashedAVVMAddresses ( ShelleyEra c) = UTxO ( ShelleyEra c) | |
StashedAVVMAddresses _ = () |
stashedAVVMAddresses :: NewEpochState era -> StashedAVVMAddresses era Source #
AVVM addresses to be removed at the end of the Shelley era. Note that the existence of this field is a hack, related to the transition of UTxO to disk. We remove AVVM addresses from the UTxO on the Shelley/Allegra boundary. However, by this point the UTxO will be moved to disk, and hence doing a scan of the UTxO for AVVM addresses will be expensive. Our solution to this is to do a scan of the UTxO on the Byron/Shelley boundary (since Byron UTxO are still on disk), stash the results here, and then remove them at the Shelley/Allegra boundary.
This is very much an awkward implementation hack, and hence we hide it from as many places as possible.
updateNES :: NewEpochState era -> BlocksMade ( Crypto era) -> LedgerState era -> NewEpochState era Source #
Update new epoch state
circulation :: EpochState era -> Coin -> Coin Source #
Calculate the current circulation
This is used in the rewards calculation, and for API endpoints for pool ranking.
Decay
decayFactor :: Float Source #
Remove Bootstrap Redeem Addresses
returnRedeemAddrsToReserves :: forall era. Era era => EpochState era -> EpochState era Source #
updateNonMyopic :: NonMyopic crypto -> Coin -> Map ( KeyHash ' StakePool crypto) Likelihood -> NonMyopic crypto Source #