Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module defines core type families which we know to vary from era to era.
Families in this module should be indexed on era.
It is intended for qualified import: > import qualified Cardano.Ledger.Core as Core
Synopsis
- class (EraTxBody era, EraTxWits era, EraTxAuxData era, EraPParams era, NoThunks (Tx era), DecCBOR (Annotator (Tx era)), EncCBOR (Tx era), ToCBOR (Tx era), Show (Tx era), Eq (Tx era), EqRaw (Tx era)) ⇒ EraTx era where
- type Tx era = (r ∷ Type) | r → era
- type TxUpgradeError era ∷ Type
- mkBasicTx ∷ TxBody era → Tx era
- bodyTxL ∷ Lens' (Tx era) (TxBody era)
- witsTxL ∷ Lens' (Tx era) (TxWits era)
- auxDataTxL ∷ Lens' (Tx era) (StrictMaybe (TxAuxData era))
- sizeTxF ∷ SimpleGetter (Tx era) Integer
- wireSizeTxF ∷ SimpleGetter (Tx era) Word32
- validateNativeScript ∷ Tx era → NativeScript era → Bool
- getMinFeeTx ∷ PParams era → Tx era → Int → Coin
- upgradeTx ∷ EraTx (PreviousEra era) ⇒ Tx (PreviousEra era) → Either (TxUpgradeError era) (Tx era)
- txIdTx ∷ EraTx era ⇒ Tx era → TxId (EraCrypto era)
- class (Val (Value era), ToJSON (TxOut era), DecCBOR (Value era), DecCBOR (CompactForm (Value era)), EncCBOR (Value era), ToCBOR (TxOut era), EncCBOR (TxOut era), DecCBOR (TxOut era), DecShareCBOR (TxOut era), Share (TxOut era) ~ Interns (Credential 'Staking (EraCrypto era)), NoThunks (TxOut era), NFData (TxOut era), Show (TxOut era), Eq (TxOut era), EraPParams era) ⇒ EraTxOut era where
- type TxOut era = (r ∷ Type) | r → era
- mkBasicTxOut ∷ HasCallStack ⇒ Addr (EraCrypto era) → Value era → TxOut era
- upgradeTxOut ∷ EraTxOut (PreviousEra era) ⇒ TxOut (PreviousEra era) → TxOut era
- valueTxOutL ∷ Lens' (TxOut era) (Value era)
- compactValueTxOutL ∷ HasCallStack ⇒ Lens' (TxOut era) (CompactForm (Value era))
- valueEitherTxOutL ∷ Lens' (TxOut era) (Either (Value era) (CompactForm (Value era)))
- addrTxOutL ∷ Lens' (TxOut era) (Addr (EraCrypto era))
- compactAddrTxOutL ∷ Lens' (TxOut era) (CompactAddr (EraCrypto era))
- addrEitherTxOutL ∷ Lens' (TxOut era) (Either (Addr (EraCrypto era)) (CompactAddr (EraCrypto era)))
- getMinCoinSizedTxOut ∷ PParams era → Sized (TxOut era) → Coin
- getMinCoinTxOut ∷ PParams era → TxOut era → Coin
- bootAddrTxOutF ∷ EraTxOut era ⇒ SimpleGetter (TxOut era) (Maybe (BootstrapAddress (EraCrypto era)))
- coinTxOutL ∷ (HasCallStack, EraTxOut era) ⇒ Lens' (TxOut era) Coin
- compactCoinTxOutL ∷ (HasCallStack, EraTxOut era) ⇒ Lens' (TxOut era) (CompactForm Coin)
- isAdaOnlyTxOutF ∷ EraTxOut era ⇒ SimpleGetter (TxOut era) Bool
- class (EraTxOut era, EraTxCert era, EraPParams era, HashAnnotated (TxBody era) EraIndependentTxBody (EraCrypto era), DecCBOR (Annotator (TxBody era)), EncCBOR (TxBody era), ToCBOR (TxBody era), NoThunks (TxBody era), NFData (TxBody era), Show (TxBody era), Eq (TxBody era), EqRaw (TxBody era)) ⇒ EraTxBody era where
- type TxBody era = (r ∷ Type) | r → era
- type TxBodyUpgradeError era ∷ Type
- mkBasicTxBody ∷ TxBody era
- inputsTxBodyL ∷ Lens' (TxBody era) (Set (TxIn (EraCrypto era)))
- outputsTxBodyL ∷ Lens' (TxBody era) (StrictSeq (TxOut era))
- feeTxBodyL ∷ Lens' (TxBody era) Coin
- withdrawalsTxBodyL ∷ Lens' (TxBody era) (Withdrawals (EraCrypto era))
- auxDataHashTxBodyL ∷ Lens' (TxBody era) (StrictMaybe (AuxiliaryDataHash (EraCrypto era)))
- spendableInputsTxBodyF ∷ SimpleGetter (TxBody era) (Set (TxIn (EraCrypto era)))
- allInputsTxBodyF ∷ SimpleGetter (TxBody era) (Set (TxIn (EraCrypto era)))
- certsTxBodyL ∷ Lens' (TxBody era) (StrictSeq (TxCert era))
- getTotalDepositsTxBody ∷ PParams era → (KeyHash 'StakePool (EraCrypto era) → Bool) → TxBody era → Coin
- getTotalRefundsTxBody ∷ PParams era → (Credential 'Staking (EraCrypto era) → Maybe Coin) → (Credential 'DRepRole (EraCrypto era) → Maybe Coin) → TxBody era → Coin
- getGenesisKeyHashCountTxBody ∷ TxBody era → Int
- upgradeTxBody ∷ EraTxBody (PreviousEra era) ⇒ TxBody (PreviousEra era) → Either (TxBodyUpgradeError era) (TxBody era)
- txIdTxBody ∷ EraTxBody era ⇒ TxBody era → TxId (EraCrypto era)
- class (Era era, Eq (TxAuxData era), EqRaw (TxAuxData era), Show (TxAuxData era), NoThunks (TxAuxData era), ToCBOR (TxAuxData era), EncCBOR (TxAuxData era), DecCBOR (Annotator (TxAuxData era)), HashAnnotated (TxAuxData era) EraIndependentTxAuxData (EraCrypto era)) ⇒ EraTxAuxData era where
- type TxAuxData era = (r ∷ Type) | r → era
- mkBasicTxAuxData ∷ TxAuxData era
- metadataTxAuxDataL ∷ Lens' (TxAuxData era) (Map Word64 Metadatum)
- upgradeTxAuxData ∷ EraTxAuxData (PreviousEra era) ⇒ TxAuxData (PreviousEra era) → TxAuxData era
- hashTxAuxData ∷ TxAuxData era → AuxiliaryDataHash (EraCrypto era)
- validateTxAuxData ∷ ProtVer → TxAuxData era → Bool
- class (EraScript era, Eq (TxWits era), EqRaw (TxWits era), Show (TxWits era), Monoid (TxWits era), NoThunks (TxWits era), ToCBOR (TxWits era), EncCBOR (TxWits era), DecCBOR (Annotator (TxWits era))) ⇒ EraTxWits era where
- type TxWits era = (r ∷ Type) | r → era
- mkBasicTxWits ∷ TxWits era
- addrTxWitsL ∷ Lens' (TxWits era) (Set (WitVKey 'Witness (EraCrypto era)))
- bootAddrTxWitsL ∷ Lens' (TxWits era) (Set (BootstrapWitness (EraCrypto era)))
- scriptTxWitsL ∷ Lens' (TxWits era) (Map (ScriptHash (EraCrypto era)) (Script era))
- upgradeTxWits ∷ EraTxWits (PreviousEra era) ⇒ TxWits (PreviousEra era) → TxWits era
- class (Era era, Show (Script era), Eq (Script era), EqRaw (Script era), ToCBOR (Script era), EncCBOR (Script era), DecCBOR (Annotator (Script era)), NoThunks (Script era), SafeToHash (Script era), Eq (NativeScript era), Show (NativeScript era), NFData (NativeScript era), NoThunks (NativeScript era), EncCBOR (NativeScript era), DecCBOR (Annotator (NativeScript era))) ⇒ EraScript era where
- type Script era = (r ∷ Type) | r → era
- type NativeScript era = (r ∷ Type) | r → era
- upgradeScript ∷ EraScript (PreviousEra era) ⇒ Script (PreviousEra era) → Script era
- scriptPrefixTag ∷ Script era → ByteString
- getNativeScript ∷ Script era → Maybe (NativeScript era)
- fromNativeScript ∷ NativeScript era → Script era
- hashScript ∷ ∀ era. EraScript era ⇒ Script era → ScriptHash (EraCrypto era)
- isNativeScript ∷ EraScript era ⇒ Script era → Bool
- hashScriptTxWitsL ∷ EraTxWits era ⇒ Lens (TxWits era) (TxWits era) (Map (ScriptHash (EraCrypto era)) (Script era)) [Script era]
- type family Value era ∷ Type
- class (Era era, Eq (PParamsHKD Identity era), Ord (PParamsHKD Identity era), Show (PParamsHKD Identity era), NFData (PParamsHKD Identity era), EncCBOR (PParamsHKD Identity era), DecCBOR (PParamsHKD Identity era), ToCBOR (PParamsHKD Identity era), FromCBOR (PParamsHKD Identity era), NoThunks (PParamsHKD Identity era), ToJSON (PParamsHKD Identity era), FromJSON (PParamsHKD Identity era), Eq (PParamsHKD StrictMaybe era), Ord (PParamsHKD StrictMaybe era), Show (PParamsHKD StrictMaybe era), NFData (PParamsHKD StrictMaybe era), EncCBOR (PParamsHKD StrictMaybe era), DecCBOR (PParamsHKD StrictMaybe era), ToCBOR (PParamsHKD StrictMaybe era), FromCBOR (PParamsHKD StrictMaybe era), NoThunks (PParamsHKD StrictMaybe era), ToJSON (PParamsHKD StrictMaybe era)) ⇒ EraPParams era where
- type PParamsHKD (f ∷ Type → Type) era = (r ∷ Type) | r → era
- type UpgradePParams (f ∷ Type → Type) era ∷ Type
- type DowngradePParams (f ∷ Type → Type) era ∷ Type
- applyPPUpdates ∷ PParams era → PParamsUpdate era → PParams era
- emptyPParamsIdentity ∷ PParamsHKD Identity era
- emptyPParamsStrictMaybe ∷ PParamsHKD StrictMaybe era
- upgradePParamsHKD ∷ (HKDApplicative f, EraPParams (PreviousEra era)) ⇒ UpgradePParams f era → PParamsHKD f (PreviousEra era) → PParamsHKD f era
- downgradePParamsHKD ∷ (HKDFunctor f, EraPParams (PreviousEra era)) ⇒ DowngradePParams f era → PParamsHKD f era → PParamsHKD f (PreviousEra era)
- hkdMinFeeAL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMinFeeBL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMaxBBSizeL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32)
- hkdMaxTxSizeL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32)
- hkdMaxBHSizeL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16)
- hkdKeyDepositL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdPoolDepositL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdEMaxL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f EpochInterval)
- hkdNOptL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Natural)
- hkdA0L ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f NonNegativeInterval)
- hkdRhoL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval)
- hkdTauL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval)
- hkdDL ∷ (HKDFunctor f, ProtVerAtMost era 6) ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval)
- ppDG ∷ SimpleGetter (PParams era) UnitInterval
- hkdExtraEntropyL ∷ (HKDFunctor f, ProtVerAtMost era 6) ⇒ Lens' (PParamsHKD f era) (HKD f Nonce)
- hkdProtocolVersionL ∷ (HKDFunctor f, ProtVerAtMost era 8) ⇒ Lens' (PParamsHKD f era) (HKD f ProtVer)
- ppProtocolVersionL ∷ Lens' (PParams era) ProtVer
- ppuProtocolVersionL ∷ ProtVerAtMost era 8 ⇒ Lens' (PParamsUpdate era) (StrictMaybe ProtVer)
- hkdMinUTxOValueL ∷ HKDFunctor f ⇒ ProtVerAtMost era 4 ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMinPoolCostL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- mkCoinTxOut ∷ EraTxOut era ⇒ Addr (EraCrypto era) → Coin → TxOut era
- class (Crypto (EraCrypto era), Typeable era, KnownNat (ProtVerLow era), KnownNat (ProtVerHigh era), ProtVerLow era <= ProtVerHigh era, MinVersion <= ProtVerLow era, MinVersion <= ProtVerHigh era, CmpNat (ProtVerLow era) MaxVersion ~ 'LT, CmpNat (ProtVerHigh era) MaxVersion ~ 'LT, ProtVerLow era <= MaxVersion, ProtVerHigh era <= MaxVersion) ⇒ Era era where
- type EraCrypto era ∷ Type
- type PreviousEra era = (r ∷ Type) | r → era
- type ProtVerLow era ∷ Nat
- type ProtVerHigh era ∷ Nat
- eraName ∷ String
- data ByronEra c
- type family EraRule (rule ∷ Symbol) era = (r ∷ Type) | r → rule
- type family EraRuleFailure (rule ∷ Symbol) era = (r ∷ Type) | r → rule era
- type family EraRuleEvent (rule ∷ Symbol) era = (r ∷ Type) | r → rule era
- data VoidEraRule (rule ∷ Symbol) era
- absurdEraRule ∷ VoidEraRule rule era → a
- class EraRuleFailure rule era ~ PredicateFailure (EraRule rule era) ⇒ InjectRuleFailure (rule ∷ Symbol) t era where
- injectFailure ∷ t era → EraRuleFailure rule era
- class EraRuleEvent rule era ~ Event (EraRule rule era) ⇒ InjectRuleEvent (rule ∷ Symbol) t era where
- injectEvent ∷ t era → EraRuleEvent rule era
- type AtMostEra (eraName ∷ Type → Type) era = ProtVerAtMost era (ProtVerHigh (eraName (EraCrypto era)))
- type AtLeastEra (eraName ∷ Type → Type) era = ProtVerAtLeast era (ProtVerLow (eraName (EraCrypto era)))
- type ExactEra (inEra ∷ Type → Type) era = ProtVerInBounds era (ProtVerLow (inEra (EraCrypto era))) (ProtVerHigh (inEra (EraCrypto era)))
- type family ProtVerAtMost era (h ∷ Nat) ∷ Constraint where ...
- type family ProtVerAtLeast era (l ∷ Nat) ∷ Constraint where ...
- type ProtVerInBounds era l h = (ProtVerAtLeast era l, ProtVerAtMost era h)
- atLeastEra ∷ AtLeastEra eraName era ⇒ ()
- atMostEra ∷ AtMostEra eraName era ⇒ ()
- notSupportedInThisEra ∷ HasCallStack ⇒ a
- notSupportedInThisEraL ∷ HasCallStack ⇒ Lens' a b
- eraProtVerLow ∷ ∀ era. Era era ⇒ Version
- eraProtVerHigh ∷ ∀ era. Era era ⇒ Version
- eraProtVersions ∷ ∀ era. Era era ⇒ [Version]
- toEraCBOR ∷ ∀ era t. (Era era, EncCBOR t) ⇒ t → Encoding
- fromEraCBOR ∷ ∀ era t s. (Era era, DecCBOR t) ⇒ Decoder s t
- fromEraShareCBOR ∷ ∀ era t s. (Era era, DecShareCBOR t) ⇒ Decoder s t
- eraDecoder ∷ ∀ era t s. Era era ⇒ Decoder s t → Decoder s t
- class (EraTx era, Eq (TxSeq era), Show (TxSeq era), EncCBORGroup (TxSeq era), DecCBOR (Annotator (TxSeq era))) ⇒ EraSegWits era where
- bBodySize ∷ ∀ era. EraSegWits era ⇒ ProtVer → TxSeq era → Int
- data RewardType
- data Reward c = Reward {
- rewardType ∷ !RewardType
- rewardPool ∷ !(KeyHash 'StakePool c)
- rewardAmount ∷ !Coin
- module Cardano.Ledger.Hashes
- class (Era era, ToJSON (TxCert era), DecCBOR (TxCert era), EncCBOR (TxCert era), ToCBOR (TxCert era), FromCBOR (TxCert era), NoThunks (TxCert era), NFData (TxCert era), Show (TxCert era), Ord (TxCert era), Eq (TxCert era)) ⇒ EraTxCert era where
- type TxCert era = (r ∷ Type) | r → era
- type TxCertUpgradeError era ∷ Type
- upgradeTxCert ∷ EraTxCert (PreviousEra era) ⇒ TxCert (PreviousEra era) → Either (TxCertUpgradeError era) (TxCert era)
- getVKeyWitnessTxCert ∷ TxCert era → Maybe (KeyHash 'Witness (EraCrypto era))
- getScriptWitnessTxCert ∷ TxCert era → Maybe (ScriptHash (EraCrypto era))
- mkRegPoolTxCert ∷ PoolParams (EraCrypto era) → TxCert era
- getRegPoolTxCert ∷ TxCert era → Maybe (PoolParams (EraCrypto era))
- mkRetirePoolTxCert ∷ KeyHash 'StakePool (EraCrypto era) → EpochNo → TxCert era
- getRetirePoolTxCert ∷ TxCert era → Maybe (KeyHash 'StakePool (EraCrypto era), EpochNo)
- lookupRegStakeTxCert ∷ TxCert era → Maybe (Credential 'Staking (EraCrypto era))
- lookupUnRegStakeTxCert ∷ TxCert era → Maybe (Credential 'Staking (EraCrypto era))
- getTotalDepositsTxCerts ∷ Foldable f ⇒ PParams era → (KeyHash 'StakePool (EraCrypto era) → Bool) → f (TxCert era) → Coin
- getTotalRefundsTxCerts ∷ Foldable f ⇒ PParams era → (Credential 'Staking (EraCrypto era) → Maybe Coin) → (Credential 'DRepRole (EraCrypto era) → Maybe Coin) → f (TxCert era) → Coin
- pattern RegPoolTxCert ∷ EraTxCert era ⇒ PoolParams (EraCrypto era) → TxCert era
- pattern RetirePoolTxCert ∷ EraTxCert era ⇒ KeyHash 'StakePool (EraCrypto era) → EpochNo → TxCert era
- data PoolCert c
- = RegPool !(PoolParams c)
- | RetirePool !(KeyHash 'StakePool c) !EpochNo
- getPoolCertTxCert ∷ EraTxCert era ⇒ TxCert era → Maybe (PoolCert (EraCrypto era))
- poolCertKeyHashWitness ∷ PoolCert c → KeyHash 'Witness c
- isRegStakeTxCert ∷ EraTxCert era ⇒ TxCert era → Bool
- isUnRegStakeTxCert ∷ EraTxCert era ⇒ TxCert era → Bool
- class (Era era, Eq (PParamsHKD Identity era), Ord (PParamsHKD Identity era), Show (PParamsHKD Identity era), NFData (PParamsHKD Identity era), EncCBOR (PParamsHKD Identity era), DecCBOR (PParamsHKD Identity era), ToCBOR (PParamsHKD Identity era), FromCBOR (PParamsHKD Identity era), NoThunks (PParamsHKD Identity era), ToJSON (PParamsHKD Identity era), FromJSON (PParamsHKD Identity era), Eq (PParamsHKD StrictMaybe era), Ord (PParamsHKD StrictMaybe era), Show (PParamsHKD StrictMaybe era), NFData (PParamsHKD StrictMaybe era), EncCBOR (PParamsHKD StrictMaybe era), DecCBOR (PParamsHKD StrictMaybe era), ToCBOR (PParamsHKD StrictMaybe era), FromCBOR (PParamsHKD StrictMaybe era), NoThunks (PParamsHKD StrictMaybe era), ToJSON (PParamsHKD StrictMaybe era)) ⇒ EraPParams era where
- type PParamsHKD (f ∷ Type → Type) era = (r ∷ Type) | r → era
- type UpgradePParams (f ∷ Type → Type) era ∷ Type
- type DowngradePParams (f ∷ Type → Type) era ∷ Type
- applyPPUpdates ∷ PParams era → PParamsUpdate era → PParams era
- emptyPParamsIdentity ∷ PParamsHKD Identity era
- emptyPParamsStrictMaybe ∷ PParamsHKD StrictMaybe era
- upgradePParamsHKD ∷ (HKDApplicative f, EraPParams (PreviousEra era)) ⇒ UpgradePParams f era → PParamsHKD f (PreviousEra era) → PParamsHKD f era
- downgradePParamsHKD ∷ (HKDFunctor f, EraPParams (PreviousEra era)) ⇒ DowngradePParams f era → PParamsHKD f era → PParamsHKD f (PreviousEra era)
- hkdMinFeeAL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMinFeeBL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMaxBBSizeL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32)
- hkdMaxTxSizeL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32)
- hkdMaxBHSizeL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16)
- hkdKeyDepositL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdPoolDepositL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdEMaxL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f EpochInterval)
- hkdNOptL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Natural)
- hkdA0L ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f NonNegativeInterval)
- hkdRhoL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval)
- hkdTauL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval)
- hkdDL ∷ (HKDFunctor f, ProtVerAtMost era 6) ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval)
- ppDG ∷ SimpleGetter (PParams era) UnitInterval
- hkdExtraEntropyL ∷ (HKDFunctor f, ProtVerAtMost era 6) ⇒ Lens' (PParamsHKD f era) (HKD f Nonce)
- hkdProtocolVersionL ∷ (HKDFunctor f, ProtVerAtMost era 8) ⇒ Lens' (PParamsHKD f era) (HKD f ProtVer)
- ppProtocolVersionL ∷ Lens' (PParams era) ProtVer
- ppuProtocolVersionL ∷ ProtVerAtMost era 8 ⇒ Lens' (PParamsUpdate era) (StrictMaybe ProtVer)
- hkdMinUTxOValueL ∷ HKDFunctor f ⇒ ProtVerAtMost era 4 ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMinPoolCostL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- newtype PParams era = PParams (PParamsHKD Identity era)
- emptyPParams ∷ EraPParams era ⇒ PParams era
- newtype PParamsUpdate era = PParamsUpdate (PParamsHKD StrictMaybe era)
- emptyPParamsUpdate ∷ EraPParams era ⇒ PParamsUpdate era
- genericApplyPPUpdates ∷ ∀ era a u. (Generic (PParamsHKD Identity era), Generic (PParamsHKD StrictMaybe era), Updatable (Rep (PParamsHKD Identity era) a) (Rep (PParamsHKD StrictMaybe era) u)) ⇒ PParams era → PParamsUpdate era → PParams era
- ppMinFeeAL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Coin
- ppMinFeeBL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Coin
- ppMaxBBSizeL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Word32
- ppMaxTxSizeL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Word32
- ppMaxBHSizeL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Word16
- ppKeyDepositL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Coin
- ppPoolDepositL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Coin
- ppEMaxL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) EpochInterval
- ppNOptL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Natural
- ppA0L ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) NonNegativeInterval
- ppRhoL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) UnitInterval
- ppTauL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) UnitInterval
- ppDL ∷ ∀ era. (EraPParams era, ProtVerAtMost era 6) ⇒ Lens' (PParams era) UnitInterval
- ppExtraEntropyL ∷ ∀ era. (EraPParams era, ProtVerAtMost era 6) ⇒ Lens' (PParams era) Nonce
- ppMinUTxOValueL ∷ ∀ era. (EraPParams era, ProtVerAtMost era 4) ⇒ Lens' (PParams era) Coin
- ppMinPoolCostL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Coin
- ppuMinFeeAL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin)
- ppuMinFeeBL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin)
- ppuMaxBBSizeL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word32)
- ppuMaxTxSizeL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word32)
- ppuMaxBHSizeL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word16)
- ppuKeyDepositL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin)
- ppuPoolDepositL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin)
- ppuEMaxL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe EpochInterval)
- ppuNOptL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Natural)
- ppuA0L ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe NonNegativeInterval)
- ppuRhoL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval)
- ppuTauL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval)
- ppuDL ∷ ∀ era. (EraPParams era, ProtVerAtMost era 6) ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval)
- ppuExtraEntropyL ∷ ∀ era. (EraPParams era, ProtVerAtMost era 6) ⇒ Lens' (PParamsUpdate era) (StrictMaybe Nonce)
- ppuMinUTxOValueL ∷ ∀ era. (EraPParams era, ProtVerAtMost era 4) ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin)
- ppuMinPoolCostL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin)
- ppLens ∷ Lens' (PParams era) (PParamsHKD Identity era)
- ppuLens ∷ Lens' (PParamsUpdate era) (PParamsHKD StrictMaybe era)
- mapPParams ∷ (PParamsHKD Identity era1 → PParamsHKD Identity era2) → PParams era1 → PParams era2
- mapPParamsUpdate ∷ (PParamsHKD StrictMaybe era1 → PParamsHKD StrictMaybe era2) → PParamsUpdate era1 → PParamsUpdate era2
- upgradePParams ∷ (EraPParams era, EraPParams (PreviousEra era)) ⇒ UpgradePParams Identity era → PParams (PreviousEra era) → PParams era
- downgradePParams ∷ (EraPParams era, EraPParams (PreviousEra era)) ⇒ DowngradePParams Identity era → PParams era → PParams (PreviousEra era)
- upgradePParamsUpdate ∷ (EraPParams era, EraPParams (PreviousEra era)) ⇒ UpgradePParams StrictMaybe era → PParamsUpdate (PreviousEra era) → PParamsUpdate era
- downgradePParamsUpdate ∷ (EraPParams era, EraPParams (PreviousEra era)) ⇒ DowngradePParams StrictMaybe era → PParamsUpdate era → PParamsUpdate (PreviousEra era)
- data PParam era where
- PParam ∷ ToPlutusData t ⇒ Word → Lens' (PParamsUpdate era) (StrictMaybe t) → PParam era
- makePParamMap ∷ [PParam era] → Map Word (PParam era)
- type family PreviousEra era = (r ∷ Type) | r → era
- type family TranslationContext era ∷ Type
- type family TranslationError era f ∷ Type
- class (Era era, Era (PreviousEra era)) ⇒ TranslateEra era f
- translateEra ∷ TranslateEra era f ⇒ TranslationContext era → f (PreviousEra era) → Except (TranslationError era f) (f era)
- translateEraMaybe ∷ (TranslateEra era f, TranslationError era f ~ ()) ⇒ TranslationContext era → f (PreviousEra era) → Maybe (f era)
- translateEra' ∷ (TranslateEra era f, TranslationError era f ~ Void) ⇒ TranslationContext era → f (PreviousEra era) → f era
- translateEraThroughCBOR ∷ ∀ era ti to. (Era era, ToCBOR (ti (PreviousEra era)), DecCBOR (Annotator (to era))) ⇒ Text → ti (PreviousEra era) → Except DecoderError (to era)
Era-changing types
class (EraTxBody era, EraTxWits era, EraTxAuxData era, EraPParams era, NoThunks (Tx era), DecCBOR (Annotator (Tx era)), EncCBOR (Tx era), ToCBOR (Tx era), Show (Tx era), Eq (Tx era), EqRaw (Tx era)) ⇒ EraTx era where Source #
A transaction.
type Tx era = (r ∷ Type) | r → era Source #
type TxUpgradeError era ∷ Type Source #
type TxUpgradeError era = Void
mkBasicTx ∷ TxBody era → Tx era Source #
bodyTxL ∷ Lens' (Tx era) (TxBody era) Source #
witsTxL ∷ Lens' (Tx era) (TxWits era) Source #
auxDataTxL ∷ Lens' (Tx era) (StrictMaybe (TxAuxData era)) Source #
sizeTxF ∷ SimpleGetter (Tx era) Integer Source #
For fee calculation and estimations of impact on block space
wireSizeTxF ∷ SimpleGetter (Tx era) Word32 Source #
For end use by eg. diffusion layer in transaction submission protocol
validateNativeScript ∷ Tx era → NativeScript era → Bool Source #
Using information from the transaction validate the supplied native script.
Minimum fee calculation excluding witnesses
upgradeTx ∷ EraTx (PreviousEra era) ⇒ Tx (PreviousEra era) → Either (TxUpgradeError era) (Tx era) Source #
class (Val (Value era), ToJSON (TxOut era), DecCBOR (Value era), DecCBOR (CompactForm (Value era)), EncCBOR (Value era), ToCBOR (TxOut era), EncCBOR (TxOut era), DecCBOR (TxOut era), DecShareCBOR (TxOut era), Share (TxOut era) ~ Interns (Credential 'Staking (EraCrypto era)), NoThunks (TxOut era), NFData (TxOut era), Show (TxOut era), Eq (TxOut era), EraPParams era) ⇒ EraTxOut era where Source #
Abstract interface into specific fields of a TxOut
mkBasicTxOut, upgradeTxOut, valueEitherTxOutL, addrEitherTxOutL, (getMinCoinSizedTxOut | getMinCoinTxOut)
mkBasicTxOut ∷ HasCallStack ⇒ Addr (EraCrypto era) → Value era → TxOut era Source #
upgradeTxOut ∷ EraTxOut (PreviousEra era) ⇒ TxOut (PreviousEra era) → TxOut era Source #
Every era, except Shelley, must be able to upgrade a TxOut
from a previous era.
valueTxOutL ∷ Lens' (TxOut era) (Value era) Source #
compactValueTxOutL ∷ HasCallStack ⇒ Lens' (TxOut era) (CompactForm (Value era)) Source #
valueEitherTxOutL ∷ Lens' (TxOut era) (Either (Value era) (CompactForm (Value era))) Source #
Lens for getting and setting in TxOut either an address or its compact version by doing the least amount of work.
addrTxOutL ∷ Lens' (TxOut era) (Addr (EraCrypto era)) Source #
compactAddrTxOutL ∷ Lens' (TxOut era) (CompactAddr (EraCrypto era)) Source #
addrEitherTxOutL ∷ Lens' (TxOut era) (Either (Addr (EraCrypto era)) (CompactAddr (EraCrypto era))) Source #
Lens for getting and setting in TxOut either an address or its compact version by doing the least amount of work.
The utility of this function comes from the fact that TxOut usually stores
the address in either one of two forms: compacted or unpacked. In order to
avoid extroneous conversions in getTxOutAddr
and getTxOutCompactAddr
we
can define just this functionality. Also sometimes it is crucial to know at
the callsite which form of address we have readily available without any
conversions (eg. searching millions of TxOuts for a particular address)
getMinCoinSizedTxOut ∷ PParams era → Sized (TxOut era) → Coin Source #
Produce the minimum lovelace that a given transaction output must
contain. Information about the size of the TxOut is required in some eras.
Use getMinCoinTxOut
if you don't have the size readily available to you.
getMinCoinTxOut ∷ PParams era → TxOut era → Coin Source #
Same as getMinCoinSizedTxOut
, except information about the size of
TxOut will be computed by serializing the TxOut. If the size turns out to
be not needed, then serialization will have no overhead, since it is
computed lazily.
bootAddrTxOutF ∷ EraTxOut era ⇒ SimpleGetter (TxOut era) (Maybe (BootstrapAddress (EraCrypto era))) Source #
coinTxOutL ∷ (HasCallStack, EraTxOut era) ⇒ Lens' (TxOut era) Coin Source #
compactCoinTxOutL ∷ (HasCallStack, EraTxOut era) ⇒ Lens' (TxOut era) (CompactForm Coin) Source #
isAdaOnlyTxOutF ∷ EraTxOut era ⇒ SimpleGetter (TxOut era) Bool Source #
This is a getter that implements an efficient way to check whether TxOut
contains ADA only.
class (EraTxOut era, EraTxCert era, EraPParams era, HashAnnotated (TxBody era) EraIndependentTxBody (EraCrypto era), DecCBOR (Annotator (TxBody era)), EncCBOR (TxBody era), ToCBOR (TxBody era), NoThunks (TxBody era), NFData (TxBody era), Show (TxBody era), Eq (TxBody era), EqRaw (TxBody era)) ⇒ EraTxBody era where Source #
mkBasicTxBody, inputsTxBodyL, outputsTxBodyL, feeTxBodyL, withdrawalsTxBodyL, auxDataHashTxBodyL, spendableInputsTxBodyF, allInputsTxBodyF, certsTxBodyL, upgradeTxBody
type TxBody era = (r ∷ Type) | r → era Source #
The body of a transaction.
type TxBodyUpgradeError era ∷ Type Source #
type TxBodyUpgradeError era = Void
mkBasicTxBody ∷ TxBody era Source #
inputsTxBodyL ∷ Lens' (TxBody era) (Set (TxIn (EraCrypto era))) Source #
outputsTxBodyL ∷ Lens' (TxBody era) (StrictSeq (TxOut era)) Source #
feeTxBodyL ∷ Lens' (TxBody era) Coin Source #
withdrawalsTxBodyL ∷ Lens' (TxBody era) (Withdrawals (EraCrypto era)) Source #
auxDataHashTxBodyL ∷ Lens' (TxBody era) (StrictMaybe (AuxiliaryDataHash (EraCrypto era))) Source #
spendableInputsTxBodyF ∷ SimpleGetter (TxBody era) (Set (TxIn (EraCrypto era))) Source #
This getter will produce all inputs from the UTxO map that this transaction might spend, which ones will depend on the validity of the transaction itself. Starting in Alonzo this will include collateral inputs.
allInputsTxBodyF ∷ SimpleGetter (TxBody era) (Set (TxIn (EraCrypto era))) Source #
This getter will produce all inputs from the UTxO map that this transaction is referencing, even if some of them cannot be spent by the transaction. For example starting with Babbage era it will also include reference inputs.
certsTxBodyL ∷ Lens' (TxBody era) (StrictSeq (TxCert era)) Source #
getTotalDepositsTxBody Source #
∷ PParams era | |
→ (KeyHash 'StakePool (EraCrypto era) → Bool) | Check whether stake pool is registered or not |
→ TxBody era | |
→ Coin |
Compute the total deposits from the certificates in a TxBody.
This is the contribution of a TxBody towards the consumed amount by the transaction
getTotalRefundsTxBody Source #
∷ PParams era | |
→ (Credential 'Staking (EraCrypto era) → Maybe Coin) | Lookup current deposit for Staking credential if one is registered |
→ (Credential 'DRepRole (EraCrypto era) → Maybe Coin) | Lookup current deposit for DRep credential if one is registered |
→ TxBody era | |
→ Coin |
Compute the total refunds from the Certs of a TxBody.
This is the contribution of a TxBody towards produced amount by the transaction
getGenesisKeyHashCountTxBody ∷ TxBody era → Int Source #
This function is not used in the ledger rules. It is only used by the downstream tooling to figure out how many witnesses should be supplied for Genesis keys.
upgradeTxBody ∷ EraTxBody (PreviousEra era) ⇒ TxBody (PreviousEra era) → Either (TxBodyUpgradeError era) (TxBody era) Source #
Upgrade the transaction body from the previous era.
This can fail where elements of the transaction body are deprecated.
Compare this to translateEraThroughCBOR
:
- upgradeTxBody
will use the Haskell representation, but will not
preserve the serialised form. However, it will be suitable for iterated
translation through eras.
- translateEraThroughCBOR
will preserve the binary representation, but is
not guaranteed to work through multiple eras - that is, the serialised
representation from era n is guaranteed valid in era n + 1, but not
necessarily in era n + 2.
class (Era era, Eq (TxAuxData era), EqRaw (TxAuxData era), Show (TxAuxData era), NoThunks (TxAuxData era), ToCBOR (TxAuxData era), EncCBOR (TxAuxData era), DecCBOR (Annotator (TxAuxData era)), HashAnnotated (TxAuxData era) EraIndependentTxAuxData (EraCrypto era)) ⇒ EraTxAuxData era where Source #
TxAuxData which may be attached to a transaction
mkBasicTxAuxData ∷ TxAuxData era Source #
metadataTxAuxDataL ∷ Lens' (TxAuxData era) (Map Word64 Metadatum) Source #
upgradeTxAuxData ∷ EraTxAuxData (PreviousEra era) ⇒ TxAuxData (PreviousEra era) → TxAuxData era Source #
Every era, except Shelley, must be able to upgrade a TxAuxData
from a previous
era.
Warning - Important to note that any memoized binary representation will not be
preserved. If you need to retain underlying bytes you can use translateEraThroughCBOR
hashTxAuxData ∷ TxAuxData era → AuxiliaryDataHash (EraCrypto era) Source #
class (EraScript era, Eq (TxWits era), EqRaw (TxWits era), Show (TxWits era), Monoid (TxWits era), NoThunks (TxWits era), ToCBOR (TxWits era), EncCBOR (TxWits era), DecCBOR (Annotator (TxWits era))) ⇒ EraTxWits era where Source #
A collection of witnesses in a Tx
mkBasicTxWits ∷ TxWits era Source #
addrTxWitsL ∷ Lens' (TxWits era) (Set (WitVKey 'Witness (EraCrypto era))) Source #
bootAddrTxWitsL ∷ Lens' (TxWits era) (Set (BootstrapWitness (EraCrypto era))) Source #
scriptTxWitsL ∷ Lens' (TxWits era) (Map (ScriptHash (EraCrypto era)) (Script era)) Source #
upgradeTxWits ∷ EraTxWits (PreviousEra era) ⇒ TxWits (PreviousEra era) → TxWits era Source #
class (Era era, Show (Script era), Eq (Script era), EqRaw (Script era), ToCBOR (Script era), EncCBOR (Script era), DecCBOR (Annotator (Script era)), NoThunks (Script era), SafeToHash (Script era), Eq (NativeScript era), Show (NativeScript era), NFData (NativeScript era), NoThunks (NativeScript era), EncCBOR (NativeScript era), DecCBOR (Annotator (NativeScript era))) ⇒ EraScript era where Source #
Typeclass for script data types. Allows for script validation and hashing.
You must understand the role of SafeToHash and scriptPrefixTag to make new
instances. scriptPrefixTag
is a magic number representing the tag of the
script language. For each new script language defined, a new tag is chosen
and the tag is included in the script hash for a script. The safeToHash
constraint ensures that Scripts are never reserialised.
type Script era = (r ∷ Type) | r → era Source #
Scripts which may lock transaction outputs in this era
type NativeScript era = (r ∷ Type) | r → era Source #
upgradeScript ∷ EraScript (PreviousEra era) ⇒ Script (PreviousEra era) → Script era Source #
Every era, except Shelley, must be able to upgrade a Script
from a previous era.
Warning - Important to note that any memoized binary representation will not be
preserved, you need to retain underlying bytes you can use translateEraThroughCBOR
scriptPrefixTag ∷ Script era → ByteString Source #
getNativeScript ∷ Script era → Maybe (NativeScript era) Source #
fromNativeScript ∷ NativeScript era → Script era Source #
hashScript ∷ ∀ era. EraScript era ⇒ Script era → ScriptHash (EraCrypto era) Source #
Compute ScriptHash
of a Script
for a particular era.
hashScriptTxWitsL ∷ EraTxWits era ⇒ Lens (TxWits era) (TxWits era) (Map (ScriptHash (EraCrypto era)) (Script era)) [Script era] Source #
This is a helper lens that will hash the scripts when adding as witnesses.
class (Era era, Eq (PParamsHKD Identity era), Ord (PParamsHKD Identity era), Show (PParamsHKD Identity era), NFData (PParamsHKD Identity era), EncCBOR (PParamsHKD Identity era), DecCBOR (PParamsHKD Identity era), ToCBOR (PParamsHKD Identity era), FromCBOR (PParamsHKD Identity era), NoThunks (PParamsHKD Identity era), ToJSON (PParamsHKD Identity era), FromJSON (PParamsHKD Identity era), Eq (PParamsHKD StrictMaybe era), Ord (PParamsHKD StrictMaybe era), Show (PParamsHKD StrictMaybe era), NFData (PParamsHKD StrictMaybe era), EncCBOR (PParamsHKD StrictMaybe era), DecCBOR (PParamsHKD StrictMaybe era), ToCBOR (PParamsHKD StrictMaybe era), FromCBOR (PParamsHKD StrictMaybe era), NoThunks (PParamsHKD StrictMaybe era), ToJSON (PParamsHKD StrictMaybe era)) ⇒ EraPParams era where Source #
emptyPParamsIdentity, emptyPParamsStrictMaybe, upgradePParamsHKD, downgradePParamsHKD, hkdMinFeeAL, hkdMinFeeBL, hkdMaxBBSizeL, hkdMaxTxSizeL, hkdMaxBHSizeL, hkdKeyDepositL, hkdPoolDepositL, hkdEMaxL, hkdNOptL, hkdA0L, hkdRhoL, hkdTauL, hkdDL, hkdExtraEntropyL, hkdProtocolVersionL, hkdMinUTxOValueL, hkdMinPoolCostL
type PParamsHKD (f ∷ Type → Type) era = (r ∷ Type) | r → era Source #
Protocol parameters where the fields are represented with a HKD
type UpgradePParams (f ∷ Type → Type) era ∷ Type Source #
applyPPUpdates ∷ PParams era → PParamsUpdate era → PParams era Source #
Applies a protocol parameters update
default applyPPUpdates ∷ ∀ a u. (Generic (PParamsHKD Identity era), Generic (PParamsHKD StrictMaybe era), Updatable (Rep (PParamsHKD Identity era) a) (Rep (PParamsHKD StrictMaybe era) u)) ⇒ PParams era → PParamsUpdate era → PParams era Source #
emptyPParamsIdentity ∷ PParamsHKD Identity era Source #
emptyPParamsStrictMaybe ∷ PParamsHKD StrictMaybe era Source #
upgradePParamsHKD ∷ (HKDApplicative f, EraPParams (PreviousEra era)) ⇒ UpgradePParams f era → PParamsHKD f (PreviousEra era) → PParamsHKD f era Source #
Upgrade PParams from previous era to the current one
downgradePParamsHKD ∷ (HKDFunctor f, EraPParams (PreviousEra era)) ⇒ DowngradePParams f era → PParamsHKD f era → PParamsHKD f (PreviousEra era) Source #
Downgrade PParams from the current era to the previous one
hkdMinFeeAL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The linear factor for the minimum fee calculation
hkdMinFeeBL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The constant factor for the minimum fee calculation
hkdMaxBBSizeL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32) Source #
Maximal block body size
hkdMaxTxSizeL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32) Source #
Maximal transaction size
hkdMaxBHSizeL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16) Source #
Maximal block header size
hkdKeyDepositL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The amount of a key registration deposit
hkdPoolDepositL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The amount of a pool registration deposit
hkdEMaxL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f EpochInterval) Source #
epoch bound on pool retirement
hkdNOptL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Natural) Source #
Desired number of pools
hkdA0L ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f NonNegativeInterval) Source #
Pool influence
hkdRhoL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Monetary expansion
hkdTauL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Treasury expansion
hkdDL ∷ (HKDFunctor f, ProtVerAtMost era 6) ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Decentralization parameter
ppDG ∷ SimpleGetter (PParams era) UnitInterval Source #
Decentralization parameter getter
default ppDG ∷ ProtVerAtMost era 6 ⇒ SimpleGetter (PParams era) UnitInterval Source #
hkdExtraEntropyL ∷ (HKDFunctor f, ProtVerAtMost era 6) ⇒ Lens' (PParamsHKD f era) (HKD f Nonce) Source #
Extra entropy
hkdProtocolVersionL ∷ (HKDFunctor f, ProtVerAtMost era 8) ⇒ Lens' (PParamsHKD f era) (HKD f ProtVer) Source #
Protocol version
ppProtocolVersionL ∷ Lens' (PParams era) ProtVer Source #
default ppProtocolVersionL ∷ ProtVerAtMost era 8 ⇒ Lens' (PParams era) ProtVer Source #
ppuProtocolVersionL ∷ ProtVerAtMost era 8 ⇒ Lens' (PParamsUpdate era) (StrictMaybe ProtVer) Source #
PParamsUpdate Protocol version
hkdMinUTxOValueL ∷ HKDFunctor f ⇒ ProtVerAtMost era 4 ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
Minimum UTxO value
hkdMinPoolCostL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
Minimum Stake Pool Cost
Era
Era
class (Crypto (EraCrypto era), Typeable era, KnownNat (ProtVerLow era), KnownNat (ProtVerHigh era), ProtVerLow era <= ProtVerHigh era, MinVersion <= ProtVerLow era, MinVersion <= ProtVerHigh era, CmpNat (ProtVerLow era) MaxVersion ~ 'LT, CmpNat (ProtVerHigh era) MaxVersion ~ 'LT, ProtVerLow era <= MaxVersion, ProtVerHigh era <= MaxVersion) ⇒ Era era where Source #
type EraCrypto era ∷ Type Source #
type PreviousEra era = (r ∷ Type) | r → era Source #
Map an era to its predecessor.
For example:
type instance PreviousEra (AllegraEra c) = ShelleyEra c
type ProtVerLow era ∷ Nat Source #
Lowest major protocol version for this era
type ProtVerHigh era ∷ Nat Source #
Highest major protocol version for this era. By default se to ProtVerLow
type ProtVerHigh era = ProtVerLow era
Textual name of the current era.
Designed to be used with TypeApplications
:
>>>
eraName @(ByronEra StandardCrypto)
Byron
This is the era that preceded Shelley era. It cannot have any other class instances,
except for Era
type class.
Instances
Crypto c ⇒ Era (ByronEra c) Source # | |
type EraCrypto (ByronEra c) Source # | |
Defined in Cardano.Ledger.Core.Era | |
type PreviousEra (ByronEra c) Source # | |
Defined in Cardano.Ledger.Core.Era | |
type ProtVerHigh (ByronEra c) Source # | |
Defined in Cardano.Ledger.Core.Era | |
type ProtVerLow (ByronEra c) Source # | |
Defined in Cardano.Ledger.Core.Era |
Rules
type family EraRuleFailure (rule ∷ Symbol) era = (r ∷ Type) | r → rule era Source #
EraRuleFailure
type family is needed for injectivity, which STS' PredicateFailure
does not provide for us unfortunately.
Instances
type EraRuleFailure "EPOCH" era Source # | |
Defined in Cardano.Ledger.Core.Era | |
type EraRuleFailure "MIR" era Source # | |
Defined in Cardano.Ledger.Core.Era | |
type EraRuleFailure "NEWEPOCH" era Source # | |
Defined in Cardano.Ledger.Core.Era | |
type EraRuleFailure "NEWPP" era Source # | |
Defined in Cardano.Ledger.Core.Era | |
type EraRuleFailure "POOLREAP" era Source # | |
Defined in Cardano.Ledger.Core.Era | |
type EraRuleFailure "RUPD" era Source # | |
Defined in Cardano.Ledger.Core.Era | |
type EraRuleFailure "SNAP" era Source # | |
Defined in Cardano.Ledger.Core.Era | |
type EraRuleFailure "TICK" era Source # | |
Defined in Cardano.Ledger.Core.Era | |
type EraRuleFailure "TICKF" era Source # | |
Defined in Cardano.Ledger.Core.Era | |
type EraRuleFailure "UPEC" era Source # | |
Defined in Cardano.Ledger.Core.Era |
type family EraRuleEvent (rule ∷ Symbol) era = (r ∷ Type) | r → rule era Source #
data VoidEraRule (rule ∷ Symbol) era Source #
This is a type with no inhabitans for the rules. It is used to indicate that a rule does not have a predicate failure as well as marking rules that have been disabled when comparing to prior eras.
Instances
absurdEraRule ∷ VoidEraRule rule era → a Source #
class EraRuleFailure rule era ~ PredicateFailure (EraRule rule era) ⇒ InjectRuleFailure (rule ∷ Symbol) t era where Source #
Nothing
injectFailure ∷ t era → EraRuleFailure rule era Source #
default injectFailure ∷ t era ~ EraRuleFailure rule era ⇒ t era → EraRuleFailure rule era Source #
class EraRuleEvent rule era ~ Event (EraRule rule era) ⇒ InjectRuleEvent (rule ∷ Symbol) t era where Source #
Nothing
injectEvent ∷ t era → EraRuleEvent rule era Source #
default injectEvent ∷ t era ~ EraRuleEvent rule era ⇒ t era → EraRuleEvent rule era Source #
Protocol Version
type AtMostEra (eraName ∷ Type → Type) era = ProtVerAtMost era (ProtVerHigh (eraName (EraCrypto era))) Source #
Restrict the era
to equal to eraName
or come before it.
type AtLeastEra (eraName ∷ Type → Type) era = ProtVerAtLeast era (ProtVerLow (eraName (EraCrypto era))) Source #
Restrict the era
to equal to eraName
or come after it
type ExactEra (inEra ∷ Type → Type) era = ProtVerInBounds era (ProtVerLow (inEra (EraCrypto era))) (ProtVerHigh (inEra (EraCrypto era))) Source #
Restrict an era to the specific era through the protocol version. This is
equivalent to (inEra (Crypto era) ~ era)
type family ProtVerAtMost era (h ∷ Nat) ∷ Constraint where ... Source #
Requirement for the era's lowest protocol version to be lower or equal to the supplied value
ProtVerAtMost era h = ProtVerIsInBounds "at most" era h (ProtVerLow era <=? h) |
type family ProtVerAtLeast era (l ∷ Nat) ∷ Constraint where ... Source #
Requirement for the era's highest protocol version to be higher or equal to the supplied value
ProtVerAtLeast era l = ProtVerIsInBounds "at least" era l (l <=? ProtVerHigh era) |
type ProtVerInBounds era l h = (ProtVerAtLeast era l, ProtVerAtMost era h) Source #
Restrict a lower and upper bounds of the protocol version for the particular era
atLeastEra ∷ AtLeastEra eraName era ⇒ () Source #
Enforce era to be at least the specified era at the type level. In other words compiler will produce type error when applied to eras prior to the specified era. This function should be used in order to avoid redundant constraints warning.
For example these will type check
>>>
atLeastEra @BabbageEra @(ConwayEra StandardCrypto)
>>>
atLeastEra @BabbageEra @(BabbageEra StandardCrypto)
However this will result in a type error
>>>
atLeastEra @BabbageEra @(AlonzoEra StandardCrypto)
atMostEra ∷ AtMostEra eraName era ⇒ () Source #
Enforce era to be at most the specified era at the type level. In other words compiler will produce type error when applied to eras prior to the specified era. This function should be used in order to avoid redundant constraints warning.
For example these will type check
>>>
atMostEra @BabbageEra @(ShelleyEra StandardCrypto)
>>>
atMostEra @AlonzoEra @(MaryEra StandardCrypto)
However this will result in a type error
>>>
atMostEra @BabbageEra @(ConwayEra StandardCrypto)
notSupportedInThisEraL ∷ HasCallStack ⇒ Lens' a b Source #
eraProtVerLow ∷ ∀ era. Era era ⇒ Version Source #
Get the value level Version
of the lowest major protocol version for the supplied era
.
eraProtVerHigh ∷ ∀ era. Era era ⇒ Version Source #
Get the value level Version
of the highest major protocol version for the supplied era
.
eraProtVersions ∷ ∀ era. Era era ⇒ [Version] Source #
List with all major versions that are used in the particular era.
fromEraCBOR ∷ ∀ era t s. (Era era, DecCBOR t) ⇒ Decoder s t Source #
Convert a type that implements DecCBOR
to plain Decoder
using the lowest
protocol version for the supplied era
This action should not be used for decoders that require access to original bytes, use
toPlainDecoder
instead.
fromEraShareCBOR ∷ ∀ era t s. (Era era, DecShareCBOR t) ⇒ Decoder s t Source #
Convert a type that implements DecShareCBOR
to plain Decoder
using the lowest
protocol version for the supplied era
This action should not be used for decoders that require access to original bytes, use
toPlainDecoder
instead.
eraDecoder ∷ ∀ era t s. Era era ⇒ Decoder s t → Decoder s t Source #
Convert a versioned Decoder
to plain a Decoder
using the lowest protocol
version for the supplied era
This action should not be used for decoders that require access to original bytes, use
toPlainDecoder
instead.
- Segregated Witness
The idea of segregated witnessing is to alter the encoding of transactions in a block such that the witnesses (the information needed to verify the validity of the transactions) can be stored separately from the body (the information needed to update the ledger state). In this way, a node which only cares about replaying transactions need not even decode the witness information.
In order to do this, we introduce two concepts:
- A TxSeq
, which represents the decoded structure of a sequence of
transactions as represented in the encoded block; that is, with witnessing,
metadata and other non-body parts split separately.
class (EraTx era, Eq (TxSeq era), Show (TxSeq era), EncCBORGroup (TxSeq era), DecCBOR (Annotator (TxSeq era))) ⇒ EraSegWits era where Source #
Indicates that an era supports segregated witnessing.
This class embodies an isomorphism between 'TxSeq era' and 'StrictSeq
(Tx era)', witnessed by fromTxSeq
and toTxSeq
.
fromTxSeq ∷ TxSeq era → StrictSeq (Tx era) Source #
toTxSeq ∷ StrictSeq (Tx era) → TxSeq era Source #
hashTxSeq ∷ TxSeq era → Hash (HASH (EraCrypto era)) EraIndependentBlockBody Source #
Get the block body hash from the TxSeq. Note that this is not a regular "hash the stored bytes" function since the block body hash forms a small Merkle tree.
numSegComponents ∷ Word64 Source #
The number of segregated components
Rewards
data RewardType Source #
The staking rewards in Cardano are all either:
- member rewards - rewards given to a registered stake credential which has delegated to a stake pool, or
- leader rewards - rewards given to a registered stake pool (in particular, given to the stake credential in the stake pool registration certificate).
See Figure 47, "Functions used in the Reward Splitting", of the formal specification for more details.
Instances
The Reward
type captures:
- if the reward is a member or leader reward
- the stake pool ID associated with the reward
- the number of Lovelace in the reward
Reward | |
|
Instances
Re-exports
module Cardano.Ledger.Hashes
class (Era era, ToJSON (TxCert era), DecCBOR (TxCert era), EncCBOR (TxCert era), ToCBOR (TxCert era), FromCBOR (TxCert era), NoThunks (TxCert era), NFData (TxCert era), Show (TxCert era), Ord (TxCert era), Eq (TxCert era)) ⇒ EraTxCert era where Source #
type TxCert era = (r ∷ Type) | r → era Source #
type TxCertUpgradeError era ∷ Type Source #
type TxCertUpgradeError era = Void
upgradeTxCert ∷ EraTxCert (PreviousEra era) ⇒ TxCert (PreviousEra era) → Either (TxCertUpgradeError era) (TxCert era) Source #
Every era, except Shelley, must be able to upgrade a TxCert
from a previous
era. However, not all certificates can be upgraded, because some eras lose some of
the certificates, thus return type is an Either
. Eg. from Babbage to Conway: MIR
and Genesis certificates were removed.
getVKeyWitnessTxCert ∷ TxCert era → Maybe (KeyHash 'Witness (EraCrypto era)) Source #
Return a witness key whenever a certificate requires one
getScriptWitnessTxCert ∷ TxCert era → Maybe (ScriptHash (EraCrypto era)) Source #
Return a ScriptHash for certificate types that require a witness
mkRegPoolTxCert ∷ PoolParams (EraCrypto era) → TxCert era Source #
getRegPoolTxCert ∷ TxCert era → Maybe (PoolParams (EraCrypto era)) Source #
mkRetirePoolTxCert ∷ KeyHash 'StakePool (EraCrypto era) → EpochNo → TxCert era Source #
getRetirePoolTxCert ∷ TxCert era → Maybe (KeyHash 'StakePool (EraCrypto era), EpochNo) Source #
lookupRegStakeTxCert ∷ TxCert era → Maybe (Credential 'Staking (EraCrypto era)) Source #
Extract staking credential from any certificate that can register such credential
lookupUnRegStakeTxCert ∷ TxCert era → Maybe (Credential 'Staking (EraCrypto era)) Source #
Extract staking credential from any certificate that can unregister such credential
getTotalDepositsTxCerts Source #
∷ Foldable f | |
⇒ PParams era | |
→ (KeyHash 'StakePool (EraCrypto era) → Bool) | Check whether stake pool is registered or not |
→ f (TxCert era) | |
→ Coin |
Compute the total deposits from a list of certificates.
getTotalRefundsTxCerts Source #
∷ Foldable f | |
⇒ PParams era | |
→ (Credential 'Staking (EraCrypto era) → Maybe Coin) | Lookup current deposit for Staking credential if one is registered |
→ (Credential 'DRepRole (EraCrypto era) → Maybe Coin) | Lookup current deposit for DRep credential if one is registered |
→ f (TxCert era) | |
→ Coin |
Compute the total refunds from a list of certificates.
pattern RegPoolTxCert ∷ EraTxCert era ⇒ PoolParams (EraCrypto era) → TxCert era Source #
pattern RetirePoolTxCert ∷ EraTxCert era ⇒ KeyHash 'StakePool (EraCrypto era) → EpochNo → TxCert era Source #
RegPool !(PoolParams c) | A stake pool registration certificate. |
RetirePool !(KeyHash 'StakePool c) !EpochNo | A stake pool retirement certificate. |
Instances
Crypto c ⇒ ToJSON (PoolCert c) Source # | |
Generic (PoolCert c) Source # | |
Show (PoolCert c) Source # | |
Crypto c ⇒ EncCBOR (PoolCert c) Source # | |
NFData (PoolCert c) Source # | |
Defined in Cardano.Ledger.Core.TxCert | |
Eq (PoolCert c) Source # | |
Ord (PoolCert c) Source # | |
Defined in Cardano.Ledger.Core.TxCert | |
NoThunks (PoolCert c) Source # | |
type Rep (PoolCert c) Source # | |
Defined in Cardano.Ledger.Core.TxCert type Rep (PoolCert c) = D1 ('MetaData "PoolCert" "Cardano.Ledger.Core.TxCert" "cardano-ledger-core-1.16.0.0-inplace" 'False) (C1 ('MetaCons "RegPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PoolParams c))) :+: C1 ('MetaCons "RetirePool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c)) :*: S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 EpochNo))) |
isRegStakeTxCert ∷ EraTxCert era ⇒ TxCert era → Bool Source #
Check if supplied TxCert is a stake registering certificate
isUnRegStakeTxCert ∷ EraTxCert era ⇒ TxCert era → Bool Source #
Check if supplied TxCert is a stake un-registering certificate
class (Era era, Eq (PParamsHKD Identity era), Ord (PParamsHKD Identity era), Show (PParamsHKD Identity era), NFData (PParamsHKD Identity era), EncCBOR (PParamsHKD Identity era), DecCBOR (PParamsHKD Identity era), ToCBOR (PParamsHKD Identity era), FromCBOR (PParamsHKD Identity era), NoThunks (PParamsHKD Identity era), ToJSON (PParamsHKD Identity era), FromJSON (PParamsHKD Identity era), Eq (PParamsHKD StrictMaybe era), Ord (PParamsHKD StrictMaybe era), Show (PParamsHKD StrictMaybe era), NFData (PParamsHKD StrictMaybe era), EncCBOR (PParamsHKD StrictMaybe era), DecCBOR (PParamsHKD StrictMaybe era), ToCBOR (PParamsHKD StrictMaybe era), FromCBOR (PParamsHKD StrictMaybe era), NoThunks (PParamsHKD StrictMaybe era), ToJSON (PParamsHKD StrictMaybe era)) ⇒ EraPParams era where Source #
emptyPParamsIdentity, emptyPParamsStrictMaybe, upgradePParamsHKD, downgradePParamsHKD, hkdMinFeeAL, hkdMinFeeBL, hkdMaxBBSizeL, hkdMaxTxSizeL, hkdMaxBHSizeL, hkdKeyDepositL, hkdPoolDepositL, hkdEMaxL, hkdNOptL, hkdA0L, hkdRhoL, hkdTauL, hkdDL, hkdExtraEntropyL, hkdProtocolVersionL, hkdMinUTxOValueL, hkdMinPoolCostL
type PParamsHKD (f ∷ Type → Type) era = (r ∷ Type) | r → era Source #
Protocol parameters where the fields are represented with a HKD
type UpgradePParams (f ∷ Type → Type) era ∷ Type Source #
applyPPUpdates ∷ PParams era → PParamsUpdate era → PParams era Source #
Applies a protocol parameters update
default applyPPUpdates ∷ ∀ a u. (Generic (PParamsHKD Identity era), Generic (PParamsHKD StrictMaybe era), Updatable (Rep (PParamsHKD Identity era) a) (Rep (PParamsHKD StrictMaybe era) u)) ⇒ PParams era → PParamsUpdate era → PParams era Source #
emptyPParamsIdentity ∷ PParamsHKD Identity era Source #
emptyPParamsStrictMaybe ∷ PParamsHKD StrictMaybe era Source #
upgradePParamsHKD ∷ (HKDApplicative f, EraPParams (PreviousEra era)) ⇒ UpgradePParams f era → PParamsHKD f (PreviousEra era) → PParamsHKD f era Source #
Upgrade PParams from previous era to the current one
downgradePParamsHKD ∷ (HKDFunctor f, EraPParams (PreviousEra era)) ⇒ DowngradePParams f era → PParamsHKD f era → PParamsHKD f (PreviousEra era) Source #
Downgrade PParams from the current era to the previous one
hkdMinFeeAL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The linear factor for the minimum fee calculation
hkdMinFeeBL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The constant factor for the minimum fee calculation
hkdMaxBBSizeL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32) Source #
Maximal block body size
hkdMaxTxSizeL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32) Source #
Maximal transaction size
hkdMaxBHSizeL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16) Source #
Maximal block header size
hkdKeyDepositL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The amount of a key registration deposit
hkdPoolDepositL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The amount of a pool registration deposit
hkdEMaxL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f EpochInterval) Source #
epoch bound on pool retirement
hkdNOptL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Natural) Source #
Desired number of pools
hkdA0L ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f NonNegativeInterval) Source #
Pool influence
hkdRhoL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Monetary expansion
hkdTauL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Treasury expansion
hkdDL ∷ (HKDFunctor f, ProtVerAtMost era 6) ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Decentralization parameter
ppDG ∷ SimpleGetter (PParams era) UnitInterval Source #
Decentralization parameter getter
default ppDG ∷ ProtVerAtMost era 6 ⇒ SimpleGetter (PParams era) UnitInterval Source #
hkdExtraEntropyL ∷ (HKDFunctor f, ProtVerAtMost era 6) ⇒ Lens' (PParamsHKD f era) (HKD f Nonce) Source #
Extra entropy
hkdProtocolVersionL ∷ (HKDFunctor f, ProtVerAtMost era 8) ⇒ Lens' (PParamsHKD f era) (HKD f ProtVer) Source #
Protocol version
ppProtocolVersionL ∷ Lens' (PParams era) ProtVer Source #
default ppProtocolVersionL ∷ ProtVerAtMost era 8 ⇒ Lens' (PParams era) ProtVer Source #
ppuProtocolVersionL ∷ ProtVerAtMost era 8 ⇒ Lens' (PParamsUpdate era) (StrictMaybe ProtVer) Source #
PParamsUpdate Protocol version
hkdMinUTxOValueL ∷ HKDFunctor f ⇒ ProtVerAtMost era 4 ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
Minimum UTxO value
hkdMinPoolCostL ∷ HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
Minimum Stake Pool Cost
Protocol parameters
PParams (PParamsHKD Identity era) |
Instances
emptyPParams ∷ EraPParams era ⇒ PParams era Source #
newtype PParamsUpdate era Source #
The type of updates to Protocol parameters
Instances
emptyPParamsUpdate ∷ EraPParams era ⇒ PParamsUpdate era Source #
genericApplyPPUpdates ∷ ∀ era a u. (Generic (PParamsHKD Identity era), Generic (PParamsHKD StrictMaybe era), Updatable (Rep (PParamsHKD Identity era) a) (Rep (PParamsHKD StrictMaybe era) u)) ⇒ PParams era → PParamsUpdate era → PParams era Source #
PParams lens
ppMinFeeAL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Coin Source #
The linear factor for the minimum fee calculation
ppMinFeeBL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Coin Source #
The constant factor for the minimum fee calculation
ppMaxBBSizeL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Word32 Source #
Maximal block body size
ppMaxTxSizeL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Word32 Source #
Maximal transaction size
ppMaxBHSizeL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Word16 Source #
Maximal block header size
ppKeyDepositL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Coin Source #
The amount of a key registration deposit
ppPoolDepositL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Coin Source #
The amount of a pool registration deposit
ppEMaxL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) EpochInterval Source #
epoch bound on pool retirement
ppA0L ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) NonNegativeInterval Source #
Pool influence
ppRhoL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) UnitInterval Source #
Monetary expansion
ppTauL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) UnitInterval Source #
Treasury expansion
ppDL ∷ ∀ era. (EraPParams era, ProtVerAtMost era 6) ⇒ Lens' (PParams era) UnitInterval Source #
Decentralization parameter
ppExtraEntropyL ∷ ∀ era. (EraPParams era, ProtVerAtMost era 6) ⇒ Lens' (PParams era) Nonce Source #
Extra entropy
ppMinUTxOValueL ∷ ∀ era. (EraPParams era, ProtVerAtMost era 4) ⇒ Lens' (PParams era) Coin Source #
Minimum UTxO value
ppMinPoolCostL ∷ ∀ era. EraPParams era ⇒ Lens' (PParams era) Coin Source #
Minimum Stake Pool Cost
PParamsUpdate lens
ppuMinFeeAL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #
The linear factor for the minimum fee calculation
ppuMinFeeBL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #
The constant factor for the minimum fee calculation
ppuMaxBBSizeL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word32) Source #
Maximal block body size
ppuMaxTxSizeL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word32) Source #
Maximal transaction size
ppuMaxBHSizeL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word16) Source #
Maximal block header size
ppuKeyDepositL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #
The amount of a key registration deposit
ppuPoolDepositL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #
The amount of a pool registration deposit
ppuEMaxL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe EpochInterval) Source #
epoch bound on pool retirement
ppuNOptL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Natural) Source #
Desired number of pools
ppuA0L ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe NonNegativeInterval) Source #
Pool influence
ppuRhoL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval) Source #
Monetary expansion
ppuTauL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval) Source #
Treasury expansion
ppuDL ∷ ∀ era. (EraPParams era, ProtVerAtMost era 6) ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval) Source #
Decentralization parameter
ppuExtraEntropyL ∷ ∀ era. (EraPParams era, ProtVerAtMost era 6) ⇒ Lens' (PParamsUpdate era) (StrictMaybe Nonce) Source #
Extra entropy
ppuMinUTxOValueL ∷ ∀ era. (EraPParams era, ProtVerAtMost era 4) ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #
Minimum UTxO value
ppuMinPoolCostL ∷ ∀ era. EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #
Minimum Stake Pool Cost
Utility
ppuLens ∷ Lens' (PParamsUpdate era) (PParamsHKD StrictMaybe era) Source #
mapPParams ∷ (PParamsHKD Identity era1 → PParamsHKD Identity era2) → PParams era1 → PParams era2 Source #
mapPParamsUpdate ∷ (PParamsHKD StrictMaybe era1 → PParamsHKD StrictMaybe era2) → PParamsUpdate era1 → PParamsUpdate era2 Source #
upgradePParams ∷ (EraPParams era, EraPParams (PreviousEra era)) ⇒ UpgradePParams Identity era → PParams (PreviousEra era) → PParams era Source #
downgradePParams ∷ (EraPParams era, EraPParams (PreviousEra era)) ⇒ DowngradePParams Identity era → PParams era → PParams (PreviousEra era) Source #
upgradePParamsUpdate ∷ (EraPParams era, EraPParams (PreviousEra era)) ⇒ UpgradePParams StrictMaybe era → PParamsUpdate (PreviousEra era) → PParamsUpdate era Source #
downgradePParamsUpdate ∷ (EraPParams era, EraPParams (PreviousEra era)) ⇒ DowngradePParams StrictMaybe era → PParamsUpdate era → PParamsUpdate (PreviousEra era) Source #
PParamsUpdate to Data
data PParam era where Source #
Pair the tag, and exisitenially hide the type of the lens for the field with that Lens'
PParam ∷ ToPlutusData t ⇒ Word → Lens' (PParamsUpdate era) (StrictMaybe t) → PParam era |
makePParamMap ∷ [PParam era] → Map Word (PParam era) Source #
Turn a list into a Map, this assures we have no duplicates.
type family PreviousEra era = (r ∷ Type) | r → era Source #
Map an era to its predecessor.
For example:
type instance PreviousEra (AllegraEra c) = ShelleyEra c
Instances
type PreviousEra (ByronEra c) Source # | |
Defined in Cardano.Ledger.Core.Era |
type family TranslationContext era ∷ Type Source #
Per-era context used for TranslateEra
.
This context will be passed to the translation instances of all types of that particular era. In practice, most instances won't need the context, but this approach makes the translation composable (as opposed to having a separate context per type).
type family TranslationError era f ∷ Type Source #
Most translations should be infallible (default instance), but we leave the door open for partial translations.
For a partial translation, override the default type to be ()
or a
concrete error type.
class (Era era, Era (PreviousEra era)) ⇒ TranslateEra era f Source #
Translation of types between eras, e.g., from Shelley to Allegra.
When era
is just a phantom type parameter, an empty standalone deriving can be used:
newtype Foo era = Foo Int instance TranslateEra (Allegra c) Foo
Note that one could use DerivingAnyClass
(deriving (TranslateEra (Allegra
c))
), but this would introduce an undesired coupling between the
era-parametric type and (a) particular era(s). The intention is to have a
module with orphan instances per era.
In most cases, the era
parameter won't be phantom, and a manual instance
will have to be written:
newtype Bar era = Bar (TxBody era) instance CC.Crypto c => TranslateEra (Allegra c) Bar where translateEra ctxt = Bar <$> translateEra ctxt -- With the following instance being in scope: instance CC.Crypto c => TranslatEra (Allegra c) TxBody
Note: we use PreviousEra
instead of NextEra
as an era definitely knows
its predecessor, but not necessarily its successor. Moreover, one could argue
that it makes more sense to define the translation from era A to era B where
era B is defined, than where era A is defined.
translateEra ∷ TranslateEra era f ⇒ TranslationContext era → f (PreviousEra era) → Except (TranslationError era f) (f era) Source #
Translate a type f
parameterised by the era from an era to the era
after it.
The translation is a given the translation context of era
.
A default instance is provided for when the two types are Coercible
.
translateEraMaybe ∷ (TranslateEra era f, TranslationError era f ~ ()) ⇒ TranslationContext era → f (PreviousEra era) → Maybe (f era) Source #
Variant of translateEra
for when TranslationError
is ()
, converting
the result to a Maybe
.
translateEra' ∷ (TranslateEra era f, TranslationError era f ~ Void) ⇒ TranslationContext era → f (PreviousEra era) → f era Source #
Variant of translateEra
for when TranslationError
is Void
and the
translation thus cannot fail.
translateEraThroughCBOR Source #
∷ ∀ era ti to. (Era era, ToCBOR (ti (PreviousEra era)), DecCBOR (Annotator (to era))) | |
⇒ Text | Label for error reporting |
→ ti (PreviousEra era) | |
→ Except DecoderError (to era) |
Translate a type through its binary representation from previous era to the current one.