Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Cardano.Ledger.State
Contents
Synopsis
- data AccountState = AccountState {
- asTreasury ∷ !Coin
- asReserves ∷ !Coin
- class CanGetUTxO t where
- utxoG ∷ SimpleGetter (t era) (UTxO era)
- class CanGetUTxO t ⇒ CanSetUTxO t where
- newtype UTxO era = UTxO {}
- class EraTx era ⇒ EraUTxO era where
- type ScriptsNeeded era = (r ∷ Type) | r → era
- getConsumedValue ∷ PParams era → (Credential 'Staking → Maybe Coin) → (Credential 'DRepRole → Maybe Coin) → UTxO era → TxBody era → Value era
- getProducedValue ∷ PParams era → (KeyHash 'StakePool → Bool) → TxBody era → Value era
- getScriptsProvided ∷ UTxO era → Tx era → ScriptsProvided era
- getScriptsNeeded ∷ UTxO era → TxBody era → ScriptsNeeded era
- getScriptsHashesNeeded ∷ ScriptsNeeded era → Set ScriptHash
- getWitsVKeyNeeded ∷ CertState era → UTxO era → TxBody era → Set (KeyHash 'Witness)
- getMinFeeTxUtxo ∷ PParams era → Tx era → UTxO era → Coin
- newtype ScriptsProvided era = ScriptsProvided {
- unScriptsProvided ∷ Map ScriptHash (Script era)
- txins ∷ EraTxBody era ⇒ TxBody era → Set TxIn
- txinLookup ∷ TxIn → UTxO era → Maybe (TxOut era)
- txInsFilter ∷ UTxO era → Set TxIn → UTxO era
- txouts ∷ ∀ era. EraTxBody era ⇒ TxBody era → UTxO era
- balance ∷ EraTxOut era ⇒ UTxO era → Value era
- coinBalance ∷ EraTxOut era ⇒ UTxO era → Coin
- sumAllValue ∷ (EraTxOut era, Foldable f) ⇒ f (TxOut era) → Value era
- sumAllCoin ∷ (EraTxOut era, Foldable f) ⇒ f (TxOut era) → Coin
- areAllAdaOnly ∷ (EraTxOut era, Foldable f) ⇒ f (TxOut era) → Bool
- verifyWitVKey ∷ Typeable kr ⇒ Hash HASH EraIndependentTxBody → WitVKey kr → Bool
- getScriptHash ∷ Addr → Maybe ScriptHash
- data IndividualPoolStake = IndividualPoolStake {}
- data PoolDistr = PoolDistr {}
- poolDistrDistrL ∷ Lens' PoolDistr (Map (KeyHash 'StakePool) IndividualPoolStake)
- poolDistrTotalL ∷ Lens' PoolDistr (CompactForm Coin)
- individualTotalPoolStakeL ∷ Lens' IndividualPoolStake (CompactForm Coin)
- newtype Stake = Stake {
- unStake ∷ VMap VB VP (Credential 'Staking) (CompactForm Coin)
- sumAllStake ∷ Stake → Coin
- sumAllStakeCompact ∷ Stake → CompactForm Coin
- sumStakePerPool ∷ VMap VB VB (Credential 'Staking) (KeyHash 'StakePool) → Stake → Map (KeyHash 'StakePool) Coin
- data SnapShot = SnapShot {
- ssStake ∷ !Stake
- ssDelegations ∷ !(VMap VB VB (Credential 'Staking) (KeyHash 'StakePool))
- ssPoolParams ∷ !(VMap VB VB (KeyHash 'StakePool) PoolParams)
- data SnapShots = SnapShots {}
- emptySnapShot ∷ SnapShot
- emptySnapShots ∷ SnapShots
- poolStake ∷ KeyHash 'StakePool → VMap VB VB (Credential 'Staking) (KeyHash 'StakePool) → Stake → Stake
- maxPool ∷ EraPParams era ⇒ PParams era → Coin → Rational → Rational → Coin
- maxPool' ∷ NonNegativeInterval → NonZero Word16 → Coin → Rational → Rational → Coin
- calculatePoolDistr ∷ SnapShot → PoolDistr
- calculatePoolDistr' ∷ (KeyHash 'StakePool → Bool) → SnapShot → PoolDistr
- calculatePoolStake ∷ (KeyHash 'StakePool → Bool) → VMap VB VB (Credential 'Staking) (KeyHash 'StakePool) → Stake → Map (KeyHash 'StakePool) Word64
- ssStakeMarkL ∷ Lens' SnapShots SnapShot
- ssStakeMarkPoolDistrL ∷ Lens' SnapShots PoolDistr
- ssStakeSetL ∷ Lens' SnapShots SnapShot
- ssStakeGoL ∷ Lens' SnapShots SnapShot
- ssFeeL ∷ Lens' SnapShots Coin
- ssStakeL ∷ Lens' SnapShot Stake
- ssStakeDistrL ∷ Lens' SnapShot (VMap VB VP (Credential 'Staking) (CompactForm Coin))
- ssDelegationsL ∷ Lens' SnapShot (VMap VB VB (Credential 'Staking) (KeyHash 'StakePool))
- ssPoolParamsL ∷ Lens' SnapShot (VMap VB VB (KeyHash 'StakePool) PoolParams)
- class (EraPParams era, Eq (GovState era), Show (GovState era), NoThunks (GovState era), NFData (GovState era), EncCBOR (GovState era), DecCBOR (GovState era), DecShareCBOR (GovState era), Share (GovState era) ~ (Interns (Credential 'Staking), Interns (KeyHash 'StakePool), Interns (Credential 'DRepRole), Interns (Credential 'HotCommitteeRole)), ToCBOR (GovState era), FromCBOR (GovState era), Default (GovState era), ToJSON (GovState era)) ⇒ EraGov era where
- type GovState era = (r ∷ Type) | r → era
- emptyGovState ∷ GovState era
- curPParamsGovStateL ∷ Lens' (GovState era) (PParams era)
- prevPParamsGovStateL ∷ Lens' (GovState era) (PParams era)
- futurePParamsGovStateL ∷ Lens' (GovState era) (FuturePParams era)
- obligationGovState ∷ GovState era → Obligations
- data FuturePParams era
- = NoPParamsUpdate
- | DefinitePParamsUpdate !(PParams era)
- | PotentialPParamsUpdate (Maybe (PParams era))
- solidifyFuturePParams ∷ FuturePParams era → FuturePParams era
- nextEpochPParams ∷ EraGov era ⇒ GovState era → PParams era
- nextEpochUpdatedPParams ∷ EraGov era ⇒ GovState era → StrictMaybe (PParams era)
- knownFuturePParams ∷ FuturePParams era → Maybe (PParams era)
Documentation
data AccountState Source #
Constructors
AccountState | |
Fields
|
Instances
class CanGetUTxO t where Source #
Minimal complete definition
Nothing
Methods
utxoG ∷ SimpleGetter (t era) (UTxO era) Source #
default utxoG ∷ CanSetUTxO t ⇒ SimpleGetter (t era) (UTxO era) Source #
Instances
CanGetUTxO UTxO Source # | |
Defined in Cardano.Ledger.State.UTxO |
class CanGetUTxO t ⇒ CanSetUTxO t where Source #
Primitives
The unspent transaction outputs.
Instances
CanGetUTxO UTxO Source # | |
Defined in Cardano.Ledger.State.UTxO | |
CanSetUTxO UTxO Source # | |
ToJSON (TxOut era) ⇒ ToJSON (UTxO era) Source # | |
Era era ⇒ Monoid (UTxO era) Source # | |
Semigroup (UTxO era) Source # | |
Generic (UTxO era) Source # | |
Show (TxOut era) ⇒ Show (UTxO era) Source # | |
(DecCBOR (TxOut era), Era era) ⇒ FromCBOR (UTxO era) Source # | |
(EncCBOR (TxOut era), Era era) ⇒ ToCBOR (UTxO era) Source # | |
(Era era, DecCBOR (TxOut era)) ⇒ DecCBOR (UTxO era) Source # | |
(DecShareCBOR (TxOut era), Share (TxOut era) ~ Interns (Credential 'Staking)) ⇒ DecShareCBOR (UTxO era) Source # | |
(Era era, EncCBOR (TxOut era)) ⇒ EncCBOR (UTxO era) Source # | |
Default (UTxO era) Source # | |
Defined in Cardano.Ledger.State.UTxO | |
(Era era, NFData (TxOut era)) ⇒ NFData (UTxO era) Source # | |
Defined in Cardano.Ledger.State.UTxO | |
(Era era, Eq (TxOut era)) ⇒ Eq (UTxO era) Source # | |
NoThunks (TxOut era) ⇒ NoThunks (UTxO era) Source # | |
type Rep (UTxO era) Source # | |
Defined in Cardano.Ledger.State.UTxO | |
type Share (UTxO era) Source # | |
class EraTx era ⇒ EraUTxO era where Source #
Associated Types
type ScriptsNeeded era = (r ∷ Type) | r → era Source #
A customizable type on per era basis for the information required to find all scripts needed for the transaction.
Methods
Arguments
∷ PParams era | |
→ (Credential 'Staking → Maybe Coin) | Function that can lookup current delegation deposits |
→ (Credential 'DRepRole → Maybe Coin) | Function that can lookup current drep deposits |
→ UTxO era | |
→ TxBody era | |
→ Value era |
Calculate all the value that is being consumed by the transaction.
Arguments
∷ PParams era | |
→ (KeyHash 'StakePool → Bool) | Check whether a pool with a supplied PoolStakeId is already registered. |
→ TxBody era | |
→ Value era |
Arguments
∷ UTxO era | For some era it is necessary to look into the UTxO to find all of the available scripts for the transaction |
→ Tx era | |
→ ScriptsProvided era |
Initial eras will look into witness set to find all of the available scripts, but starting with Babbage we can look for available scripts in the UTxO using reference inputs.
getScriptsNeeded ∷ UTxO era → TxBody era → ScriptsNeeded era Source #
Produce all the information required for figuring out which scripts are required for the transaction to be valid, once those scripts are evaluated
getScriptsHashesNeeded ∷ ScriptsNeeded era → Set ScriptHash Source #
Extract the set of all script hashes that are needed for script validation.
getWitsVKeyNeeded ∷ CertState era → UTxO era → TxBody era → Set (KeyHash 'Witness) Source #
Extract all of the KeyHash witnesses that are required for validating the transaction
getMinFeeTxUtxo ∷ PParams era → Tx era → UTxO era → Coin Source #
Minimum fee computation, excluding witnesses and including ref scripts size
newtype ScriptsProvided era Source #
The only reason it is a newtype instead of just a Map is becuase for later eras is expensive to compute the actual map, so we want to use the type safety guidance to avoid redundant work.
Constructors
ScriptsProvided | |
Fields
|
Instances
Functions
txins ∷ EraTxBody era ⇒ TxBody era → Set TxIn Source #
Compute the UTxO inputs of a transaction. txins has the same problems as txouts, see notes below.
Filter out TxIn's from the UTxO
map
txouts ∷ ∀ era. EraTxBody era ⇒ TxBody era → UTxO era Source #
Compute the transaction outputs of a transaction.
balance ∷ EraTxOut era ⇒ UTxO era → Value era Source #
Determine the total balance contained in the UTxO.
coinBalance ∷ EraTxOut era ⇒ UTxO era → Coin Source #
Determine the total Ada only balance contained in the UTxO. This is equivalent to `coin . balance`, but it will be more efficient
sumAllValue ∷ (EraTxOut era, Foldable f) ⇒ f (TxOut era) → Value era Source #
Sum all the value in any Foldable with TxOut
s
areAllAdaOnly ∷ (EraTxOut era, Foldable f) ⇒ f (TxOut era) → Bool Source #
Check whether any of the supplied TxOut
s contain any MultiAssets. Returns
True if non of them do.
verifyWitVKey ∷ Typeable kr ⇒ Hash HASH EraIndependentTxBody → WitVKey kr → Bool Source #
Verify a transaction body witness
getScriptHash ∷ Addr → Maybe ScriptHash Source #
Extract script hash from value address with script.
data IndividualPoolStake Source #
The IndividualPoolStake
contains all the stake controlled
by a single stake pool (the combination of owners and delegates)
for a given epoch, and also the hash of the stake pool's
registered VRF key.
When a stake pool produces a block, the header contains the
full VRF verification key and VRF value for leader election.
We check the VRF key against the value in IndividualPoolStake
and we check the VRF value using the epoch nonce and
the relative stake of the pool as given in IndividualPoolStake
.
The stake is relative to the total amount of active stake
in the network. Stake is active if it is both registered and
delegated to a registered stake pool.
Constructors
IndividualPoolStake | |
Fields
|
Instances
A map of stake pool IDs (the hash of the stake pool operator's
verification key) to IndividualPoolStake
. Also holds absolute values
necessary for the calculations in the computeDRepDistr
.
Constructors
PoolDistr | |
Fields
|
Instances
ToJSON PoolDistr Source # | |
Generic PoolDistr Source # | |
Show PoolDistr Source # | |
DecCBOR PoolDistr Source # | |
EncCBOR PoolDistr Source # | |
NFData PoolDistr Source # | |
Defined in Cardano.Ledger.State.PoolDistr | |
Eq PoolDistr Source # | |
NoThunks PoolDistr Source # | |
type Rep PoolDistr Source # | |
Defined in Cardano.Ledger.State.PoolDistr type Rep PoolDistr = D1 ('MetaData "PoolDistr" "Cardano.Ledger.State.PoolDistr" "cardano-ledger-core-1.17.0.0-inplace" 'False) (C1 ('MetaCons "PoolDistr" 'PrefixI 'True) (S1 ('MetaSel ('Just "unPoolDistr") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (KeyHash 'StakePool) IndividualPoolStake)) :*: S1 ('MetaSel ('Just "pdTotalActiveStake") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (CompactForm Coin)))) |
Type of stake as map from hash key to coins associated.
Constructors
Stake | |
Fields
|
Instances
ToJSON Stake Source # | |
Generic Stake Source # | |
Show Stake Source # | |
DecShareCBOR Stake Source # | |
EncCBOR Stake Source # | |
NFData Stake Source # | |
Defined in Cardano.Ledger.State.SnapShots | |
Eq Stake Source # | |
NoThunks Stake Source # | |
type Rep Stake Source # | |
Defined in Cardano.Ledger.State.SnapShots type Rep Stake = D1 ('MetaData "Stake" "Cardano.Ledger.State.SnapShots" "cardano-ledger-core-1.17.0.0-inplace" 'True) (C1 ('MetaCons "Stake" 'PrefixI 'True) (S1 ('MetaSel ('Just "unStake") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (VMap VB VP (Credential 'Staking) (CompactForm Coin))))) | |
type Share Stake Source # | |
sumAllStake ∷ Stake → Coin Source #
sumStakePerPool ∷ VMap VB VB (Credential 'Staking) (KeyHash 'StakePool) → Stake → Map (KeyHash 'StakePool) Coin Source #
Snapshot of the stake distribution.
Constructors
SnapShot | |
Fields
|
Instances
ToJSON SnapShot Source # | |
Generic SnapShot Source # | |
Show SnapShot Source # | |
DecShareCBOR SnapShot Source # | |
EncCBOR SnapShot Source # | |
NFData SnapShot Source # | |
Defined in Cardano.Ledger.State.SnapShots | |
Eq SnapShot Source # | |
NoThunks SnapShot Source # | |
type Rep SnapShot Source # | |
Defined in Cardano.Ledger.State.SnapShots type Rep SnapShot = D1 ('MetaData "SnapShot" "Cardano.Ledger.State.SnapShots" "cardano-ledger-core-1.17.0.0-inplace" 'False) (C1 ('MetaCons "SnapShot" 'PrefixI 'True) (S1 ('MetaSel ('Just "ssStake") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Stake) :*: (S1 ('MetaSel ('Just "ssDelegations") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VMap VB VB (Credential 'Staking) (KeyHash 'StakePool))) :*: S1 ('MetaSel ('Just "ssPoolParams") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (VMap VB VB (KeyHash 'StakePool) PoolParams))))) | |
type Share SnapShot Source # | |
Snapshots of the stake distribution.
Note that ssStakeMark and ssStakeMarkPoolDistr are lazy on purpose since we only want to force the thunk after one stability window when we know that they are stable (so that we do not compute them if we do not have to). See more info in the Optimize TICKF ADR
Constructors
SnapShots | |
Fields |
Instances
ToJSON SnapShots Source # | |
Generic SnapShots Source # | |
Show SnapShots Source # | |
DecCBOR SnapShots Source # | |
DecShareCBOR SnapShots Source # | |
EncCBOR SnapShots Source # | |
Default SnapShots Source # | |
Defined in Cardano.Ledger.State.SnapShots | |
NFData SnapShots Source # | |
Defined in Cardano.Ledger.State.SnapShots | |
Eq SnapShots Source # | |
NoThunks SnapShots Source # | |
type Rep SnapShots Source # | |
Defined in Cardano.Ledger.State.SnapShots type Rep SnapShots = D1 ('MetaData "SnapShots" "Cardano.Ledger.State.SnapShots" "cardano-ledger-core-1.17.0.0-inplace" 'False) (C1 ('MetaCons "SnapShots" 'PrefixI 'True) ((S1 ('MetaSel ('Just "ssStakeMark") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SnapShot) :*: S1 ('MetaSel ('Just "ssStakeMarkPoolDistr") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PoolDistr)) :*: (S1 ('MetaSel ('Just "ssStakeSet") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SnapShot) :*: (S1 ('MetaSel ('Just "ssStakeGo") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 SnapShot) :*: S1 ('MetaSel ('Just "ssFee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))))) | |
type Share SnapShots Source # | |
poolStake ∷ KeyHash 'StakePool → VMap VB VB (Credential 'Staking) (KeyHash 'StakePool) → Stake → Stake Source #
Get stake of one pool
maxPool' ∷ NonNegativeInterval → NonZero Word16 → Coin → Rational → Rational → Coin Source #
Calculate maximal pool reward
calculatePoolStake ∷ (KeyHash 'StakePool → Bool) → VMap VB VB (Credential 'Staking) (KeyHash 'StakePool) → Stake → Map (KeyHash 'StakePool) Word64 Source #
Sum up the Coin (as CompactForm Coin = Word64) for each StakePool
ssStakeDistrL ∷ Lens' SnapShot (VMap VB VP (Credential 'Staking) (CompactForm Coin)) Source #
class (EraPParams era, Eq (GovState era), Show (GovState era), NoThunks (GovState era), NFData (GovState era), EncCBOR (GovState era), DecCBOR (GovState era), DecShareCBOR (GovState era), Share (GovState era) ~ (Interns (Credential 'Staking), Interns (KeyHash 'StakePool), Interns (Credential 'DRepRole), Interns (Credential 'HotCommitteeRole)), ToCBOR (GovState era), FromCBOR (GovState era), Default (GovState era), ToJSON (GovState era)) ⇒ EraGov era where Source #
Minimal complete definition
curPParamsGovStateL, prevPParamsGovStateL, futurePParamsGovStateL, obligationGovState
Methods
emptyGovState ∷ GovState era Source #
Construct empty governance state
curPParamsGovStateL ∷ Lens' (GovState era) (PParams era) Source #
Lens for accessing current protocol parameters
prevPParamsGovStateL ∷ Lens' (GovState era) (PParams era) Source #
Lens for accessing the previous protocol parameters
futurePParamsGovStateL ∷ Lens' (GovState era) (FuturePParams era) Source #
Lens for accessing the future protocol parameters.
This lens will produce DefinitePParamsUpdate
whenever we are absolutely sure that
the new PParams will be updated. Which means there will be no chance of a
DefinitePParamsUpdate
value until we are past the point of no return, which is 2
stability windows before the end of the epoch. This lens is mostly intended for
ledger usage and nextEpochUpdatedPParams
should be used instead whenever definite
results are desired.
obligationGovState ∷ GovState era → Obligations Source #
data FuturePParams era Source #
Constructors
NoPParamsUpdate | This indicates that there is definitely not going to be an update to PParams expected at the next epoch boundary. |
DefinitePParamsUpdate !(PParams era) | This case specifies the PParams that will be adopted at the next epoch boundary. |
PotentialPParamsUpdate (Maybe (PParams era)) | With this case there is no guarantee that these will be the new PParams, users
should not rely on this value to be computed efficiently and should use
|
Instances
solidifyFuturePParams ∷ FuturePParams era → FuturePParams era Source #
nextEpochPParams ∷ EraGov era ⇒ GovState era → PParams era Source #
This function is guaranteed to produce PParams
that will be adopted at the next
epoch boundary, whenever this function is applied to the GovState
that was produced
by ledger at any point that is two stability windows before the end of the epoch. If
you need to know if there were actual changes to those PParams then use
nextEpochUpdatedPParams
instead.
nextEpochUpdatedPParams ∷ EraGov era ⇒ GovState era → StrictMaybe (PParams era) Source #
This function is guaranteed to return updated PParams when it is called during the
last two stability windows of the epoch and there were proposals to update PParams that
all relevant parties reached consensus on. In other words whenever there is a definite
update to PParams coming on the epoch boundary those PParams will be returned,
otherwise it will return Nothing
. This function is inexpensive and can be invoked at
any time without danger of forcing some suspended computation.
knownFuturePParams ∷ FuturePParams era → Maybe (PParams era) Source #
Return new PParams only when it is known that there was an update proposed and it is guaranteed to be applied