| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Cardano.Ledger.Core
Description
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
- data TxLevel
- data STxTopLevel (l ∷ TxLevel) era where
- STopTxOnly ∷ ∀ era. STxTopLevel 'TopTx era
- withSTxTopLevelM ∷ ∀ (l ∷ TxLevel) era a m. (Typeable l, Era era, MonadFail m) ⇒ (STxTopLevel l era → m a) → m a
- data STxBothLevels (l ∷ TxLevel) era where
- STopTx ∷ ∀ era. STxBothLevels 'TopTx era
- SSubTx ∷ ∀ era. STxBothLevels 'SubTx era
- withSTxBothLevels ∷ ∀ (l ∷ TxLevel) era a. (Typeable l, HasCallStack) ⇒ (STxBothLevels l era → a) → a
- class Era era ⇒ EraTxLevel era where
- class EraTxLevel era ⇒ HasEraTxLevel (t ∷ TxLevel → Type → Type) era where
- toSTxLevel ∷ ∀ (l ∷ TxLevel). t l era → STxLevel l era
- asSTxTopLevel ∷ ∀ (l ∷ TxLevel) t era. (Typeable l, HasEraTxLevel t era, STxLevel l era ~ STxTopLevel l era) ⇒ t 'TopTx era → t l era
- mkSTxTopLevelM ∷ ∀ (l ∷ TxLevel) t m era. (Typeable l, Monad m, HasEraTxLevel t era, STxLevel l era ~ STxTopLevel l era) ⇒ m (t 'TopTx era) → m (t l era)
- withTopTxLevelOnly ∷ ∀ t era (l ∷ TxLevel) a. (HasEraTxLevel t era, STxLevel l era ~ STxTopLevel l era) ⇒ t l era → (t 'TopTx era → a) → a
- asSTxBothLevels ∷ ∀ (l ∷ TxLevel) t era. (Typeable l, HasEraTxLevel t era, STxLevel l era ~ STxBothLevels l era) ⇒ t 'TopTx era → t 'SubTx era → t l era
- mkSTxBothLevelsM ∷ ∀ (l ∷ TxLevel) t m era. (Typeable l, Monad m, HasEraTxLevel t era, STxLevel l era ~ STxBothLevels l era) ⇒ m (t 'TopTx era) → m (t 'SubTx era) → m (t l era)
- withBothTxLevels ∷ ∀ t era (l ∷ TxLevel) a. (HasEraTxLevel t era, STxLevel l era ~ STxBothLevels l era) ⇒ t l era → (t 'TopTx era → a) → (t 'SubTx era → a) → a
- data TopTx ∷ TxLevel
- data SubTx ∷ TxLevel
- type family STxLevel (l ∷ TxLevel) era = (r ∷ Type) | r → era
- class (EraTxBody era, EraTxWits era, EraTxAuxData era, EraPParams era, HasEraTxLevel Tx era, ∀ (l ∷ TxLevel). Typeable l ⇒ NoThunks (Tx l era), ∀ (l ∷ TxLevel). Typeable l ⇒ DecCBOR (Annotator (Tx l era)), ∀ (l ∷ TxLevel). Typeable l ⇒ ToCBOR (Tx l era), ∀ (l ∷ TxLevel). EncCBOR (Tx l era), ∀ (l ∷ TxLevel). NFData (Tx l era), ∀ (l ∷ TxLevel). Show (Tx l era), ∀ (l ∷ TxLevel). Eq (Tx l era)) ⇒ EraTx era where
- data Tx (l ∷ TxLevel) era
- mkBasicTx ∷ ∀ (l ∷ TxLevel). TxBody l era → Tx l era
- bodyTxL ∷ ∀ (l ∷ TxLevel). Lens' (Tx l era) (TxBody l era)
- witsTxL ∷ ∀ (l ∷ TxLevel). Lens' (Tx l era) (TxWits era)
- auxDataTxL ∷ ∀ (l ∷ TxLevel). Lens' (Tx l era) (StrictMaybe (TxAuxData era))
- sizeTxF ∷ ∀ (l ∷ TxLevel). HasCallStack ⇒ SimpleGetter (Tx l era) Word32
- sizeTxForFeeCalculation ∷ ∀ (l ∷ TxLevel). (HasCallStack, SafeToHash (TxWits era), Typeable l) ⇒ Tx l era → Word32
- validateNativeScript ∷ ∀ (l ∷ TxLevel). Tx l era → NativeScript era → Bool
- getMinFeeTx ∷ ∀ (l ∷ TxLevel). PParams era → Tx l era → Int → Coin
- txIdTx ∷ ∀ era (l ∷ TxLevel). EraTx era ⇒ Tx l era → TxId
- class (Val (Value era), ToJSON (TxOut era), DecCBOR (Value era), DecCBOR (CompactForm (Value era)), MemPack (CompactForm (Value era)), EncCBOR (Value era), ToCBOR (TxOut era), EncCBOR (TxOut era), DecCBOR (TxOut era), DecShareCBOR (TxOut era), Share (TxOut era) ~ Interns (Credential 'Staking), NoThunks (TxOut era), NFData (TxOut era), Show (TxOut era), Eq (TxOut era), MemPack (TxOut era), EraPParams era) ⇒ EraTxOut era where
- type TxOut era = (r ∷ Type) | r → era
- mkBasicTxOut ∷ Addr → Value era → TxOut era
- upgradeTxOut ∷ TxOut (PreviousEra era) → TxOut era
- valueTxOutL ∷ Lens' (TxOut era) (Value era)
- compactValueTxOutL ∷ Lens' (TxOut era) (CompactForm (Value era))
- valueEitherTxOutL ∷ Lens' (TxOut era) (Either (Value era) (CompactForm (Value era)))
- addrTxOutL ∷ Lens' (TxOut era) Addr
- compactAddrTxOutL ∷ Lens' (TxOut era) CompactAddr
- addrEitherTxOutL ∷ Lens' (TxOut era) (Either Addr CompactAddr)
- getMinCoinSizedTxOut ∷ PParams era → Sized (TxOut era) → Coin
- getMinCoinTxOut ∷ PParams era → TxOut era → Coin
- bootAddrTxOutF ∷ EraTxOut era ⇒ SimpleGetter (TxOut era) (Maybe BootstrapAddress)
- 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, HasEraTxLevel TxBody era, ∀ (l ∷ TxLevel). HashAnnotated (TxBody l era) EraIndependentTxBody, ∀ (l ∷ TxLevel). EncCBOR (TxBody l era), ∀ (l ∷ TxLevel). Typeable l ⇒ DecCBOR (Annotator (TxBody l era)), ∀ (l ∷ TxLevel). Typeable l ⇒ ToCBOR (TxBody l era), ∀ (l ∷ TxLevel). Typeable l ⇒ NoThunks (TxBody l era), ∀ (l ∷ TxLevel). NFData (TxBody l era), ∀ (l ∷ TxLevel). Show (TxBody l era), ∀ (l ∷ TxLevel). Eq (TxBody l era), ∀ (l ∷ TxLevel). EqRaw (TxBody l era)) ⇒ EraTxBody era where
- data TxBody (l ∷ TxLevel) era
- mkBasicTxBody ∷ ∀ (l ∷ TxLevel). Typeable l ⇒ TxBody l era
- inputsTxBodyL ∷ ∀ (l ∷ TxLevel). Lens' (TxBody l era) (Set TxIn)
- outputsTxBodyL ∷ ∀ (l ∷ TxLevel). Lens' (TxBody l era) (StrictSeq (TxOut era))
- feeTxBodyL ∷ Lens' (TxBody 'TopTx era) Coin
- withdrawalsTxBodyL ∷ ∀ (l ∷ TxLevel). Lens' (TxBody l era) Withdrawals
- auxDataHashTxBodyL ∷ ∀ (l ∷ TxLevel). Lens' (TxBody l era) (StrictMaybe TxAuxDataHash)
- spendableInputsTxBodyF ∷ ∀ (l ∷ TxLevel). SimpleGetter (TxBody l era) (Set TxIn)
- allInputsTxBodyF ∷ SimpleGetter (TxBody 'TopTx era) (Set TxIn)
- certsTxBodyL ∷ ∀ (l ∷ TxLevel). Lens' (TxBody l era) (StrictSeq (TxCert era))
- getTotalDepositsTxBody ∷ ∀ (l ∷ TxLevel). PParams era → (KeyHash 'StakePool → Bool) → TxBody l era → Coin
- getTotalRefundsTxBody ∷ ∀ (l ∷ TxLevel). PParams era → (Credential 'Staking → Maybe Coin) → (Credential 'DRepRole → Maybe Coin) → TxBody l era → Coin
- getGenesisKeyHashCountTxBody ∷ TxBody 'TopTx era → Int
- txIdTxBody ∷ ∀ era (l ∷ TxLevel). EraTxBody era ⇒ TxBody l era → TxId
- 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) ⇒ EraTxAuxData era where
- type TxAuxData era = (r ∷ Type) | r → era
- mkBasicTxAuxData ∷ TxAuxData era
- metadataTxAuxDataL ∷ Lens' (TxAuxData era) (Map Word64 Metadatum)
- validateTxAuxData ∷ ProtVer → TxAuxData era → Bool
- hashTxAuxData ∷ EraTxAuxData era ⇒ TxAuxData era → TxAuxDataHash
- 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))
- bootAddrTxWitsL ∷ Lens' (TxWits era) (Set BootstrapWitness)
- scriptTxWitsL ∷ Lens' (TxWits era) (Map ScriptHash (Script 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), ToCBOR (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 ∷ Script (PreviousEra era) → Script era
- scriptPrefixTag ∷ Script era → ByteString
- getNativeScript ∷ Script era → Maybe (NativeScript era)
- fromNativeScript ∷ NativeScript era → Script era
- hashScript ∷ EraScript era ⇒ Script era → ScriptHash
- isNativeScript ∷ EraScript era ⇒ Script era → Bool
- hashScriptTxWitsL ∷ EraTxWits era ⇒ Lens (TxWits era) (TxWits era) (Map ScriptHash (Script era)) [Script era]
- keyHashWitnessesTxWits ∷ EraTxWits era ⇒ TxWits era → Set (KeyHash 'Witness)
- type family Value era
- class (Era era, Eq (PParamsHKD Identity era), Ord (PParamsHKD Identity era), Show (PParamsHKD Identity era), NFData (PParamsHKD Identity era), NoThunks (PParamsHKD Identity era), Eq (PParamsHKD StrictMaybe era), Ord (PParamsHKD StrictMaybe era), Show (PParamsHKD StrictMaybe era), NFData (PParamsHKD StrictMaybe era), NoThunks (PParamsHKD StrictMaybe era)) ⇒ EraPParams era where
- type PParamsHKD (f ∷ Type → Type) era = (r ∷ Type) | r → era
- type UpgradePParams (f ∷ Type → Type) era
- type DowngradePParams (f ∷ Type → Type) era
- applyPPUpdates ∷ PParams era → PParamsUpdate era → PParams era
- emptyPParamsIdentity ∷ PParamsHKD Identity era
- emptyPParamsStrictMaybe ∷ PParamsHKD StrictMaybe era
- emptyUpgradePParamsUpdate ∷ UpgradePParams StrictMaybe era
- upgradePParamsHKD ∷ ∀ (f ∷ Type → Type). (HKDApplicative f, EraPParams (PreviousEra era)) ⇒ UpgradePParams f era → PParamsHKD f (PreviousEra era) → PParamsHKD f era
- downgradePParamsHKD ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, EraPParams (PreviousEra era)) ⇒ DowngradePParams f era → PParamsHKD f era → PParamsHKD f (PreviousEra era)
- hkdMinFeeAL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMinFeeBL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMaxBBSizeL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32)
- hkdMaxTxSizeL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32)
- hkdMaxBHSizeL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16)
- hkdKeyDepositL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdPoolDepositCompactL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f (CompactForm Coin))
- hkdEMaxL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f EpochInterval)
- hkdNOptL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16)
- hkdA0L ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f NonNegativeInterval)
- hkdRhoL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval)
- hkdTauL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval)
- hkdDL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval)
- ppDG ∷ SimpleGetter (PParams era) UnitInterval
- hkdExtraEntropyL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsHKD f era) (HKD f Nonce)
- hkdProtocolVersionL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Babbage" era) ⇒ Lens' (PParamsHKD f era) (HKD f ProtVer)
- ppProtocolVersionL ∷ Lens' (PParams era) ProtVer
- ppuProtocolVersionL ∷ Lens' (PParamsUpdate era) (StrictMaybe ProtVer)
- hkdMinUTxOValueL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Mary" era) ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMinPoolCostL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- eraPParams ∷ [PParam era]
- mkCoinTxOut ∷ EraTxOut era ⇒ Addr → Coin → TxOut era
- wireSizeTxF ∷ ∀ era (l ∷ TxLevel). EraTx era ⇒ SimpleGetter (Tx l era) Word32
- binaryUpgradeTx ∷ ∀ era (l ∷ TxLevel). (Era era, ToCBOR (Tx l (PreviousEra era)), DecCBOR (Annotator (Tx l era))) ⇒ Tx l (PreviousEra era) → Except DecoderError (Tx l era)
- binaryUpgradeTxBody ∷ ∀ era (l ∷ TxLevel). (Era era, ToCBOR (TxBody l (PreviousEra era)), DecCBOR (Annotator (TxBody l era))) ⇒ TxBody l (PreviousEra era) → Except DecoderError (TxBody l era)
- binaryUpgradeTxWits ∷ (Era era, ToCBOR (TxWits (PreviousEra era)), DecCBOR (Annotator (TxWits era))) ⇒ TxWits (PreviousEra era) → Except DecoderError (TxWits era)
- binaryUpgradeTxAuxData ∷ (Era era, ToCBOR (TxAuxData (PreviousEra era)), DecCBOR (Annotator (TxAuxData era))) ⇒ TxAuxData (PreviousEra era) → Except DecoderError (TxAuxData era)
- fromStrictMaybeL ∷ ∀ a f. Functor f ⇒ (Maybe a → f (Maybe a)) → StrictMaybe a → f (StrictMaybe a)
- toStrictMaybeL ∷ ∀ a f. Functor f ⇒ (StrictMaybe a → f (StrictMaybe a)) → Maybe a → f (Maybe a)
- data ByronEra
- class (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) ⇒ Era era where
- type EraName era ∷ Symbol
- type PreviousEra era = (r ∷ Type) | r → era
- type ProtVerLow era ∷ Nat
- type ProtVerHigh era ∷ Nat
- eraName ∷ String
- type family EraName era ∷ Symbol
- type family PreviousEra era = (r ∷ Type) | r → era
- type family ProtVerLow era ∷ Nat
- type family ProtVerHigh era ∷ Nat
- eraProtVerLow ∷ Era era ⇒ Version
- 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 ∷ ∀ (rule ∷ Symbol) era a. VoidEraRule rule era → a
- class EraRuleFailure rule era ~ PredicateFailure (EraRule rule era) ⇒ InjectRuleFailure (rule ∷ Symbol) (t ∷ Type → Type) era where
- injectFailure ∷ t era → EraRuleFailure rule era
- class EraRuleEvent rule era ~ Event (EraRule rule era) ⇒ InjectRuleEvent (rule ∷ Symbol) (t ∷ Type → Type) era where
- injectEvent ∷ t era → EraRuleEvent rule era
- type AtMostEra (eraMostEra ∷ Symbol) era = ProtVerAtMost era (ProtVerHigh (EraFromName eraMostEra))
- type AtLeastEra (atLeastEra ∷ Symbol) era = ProtVerAtLeast era (ProtVerLow (EraFromName atLeastEra))
- type ExactEra inEra era = ProtVerInBounds era (ProtVerLow inEra) (ProtVerHigh inEra)
- type family ProtVerAtMost era (h ∷ Nat) where ...
- type family ProtVerAtLeast era (l ∷ Nat) where ...
- type ProtVerInBounds era (l ∷ Nat) (h ∷ Nat) = (ProtVerAtLeast era l, ProtVerAtMost era h)
- atLeastEra ∷ ∀ (eraName ∷ Symbol) era. AtLeastEra eraName era ⇒ ()
- atMostEra ∷ ∀ (eraName ∷ Symbol) era. AtMostEra eraName era ⇒ ()
- notSupportedInThisEra ∷ HasCallStack ⇒ a
- notSupportedInThisEraL ∷ HasCallStack ⇒ Lens' a b
- eraProtVerHigh ∷ Era era ⇒ Version
- eraProtVersions ∷ Era era ⇒ [Version]
- toEraCBOR ∷ (Era era, EncCBOR t) ⇒ t → Encoding
- fromEraCBOR ∷ (Era era, DecCBOR t) ⇒ Decoder s t
- fromEraShareCBOR ∷ (Era era, DecShareCBOR t) ⇒ Decoder s t
- eraDecoder ∷ ∀ era t s. Era era ⇒ Decoder s t → Decoder s t
- eraDecoderWithBytes ∷ ∀ era t s. Era era ⇒ ByteString → Decoder s t → Decoder s t
- class (EraTx era, Eq (BlockBody era), Show (BlockBody era), Typeable (BlockBody era), EncCBORGroup (BlockBody era), DecCBOR (Annotator (BlockBody era))) ⇒ EraBlockBody era where
- type BlockBody era = (r ∷ Type) | r → era
- mkBasicBlockBody ∷ BlockBody era
- txSeqBlockBodyL ∷ Lens' (BlockBody era) (StrictSeq (Tx 'TopTx era))
- hashBlockBody ∷ BlockBody era → Hash HASH EraIndependentBlockBody
- numSegComponents ∷ Word64
- bBodySize ∷ EraBlockBody era ⇒ ProtVer → BlockBody era → Int
- data RewardType
- data Reward = Reward {
- rewardType ∷ !RewardType
- rewardPool ∷ !(KeyHash 'StakePool)
- rewardAmount ∷ !Coin
- data KeyRole
- data Witness ∷ KeyRole
- data Payment ∷ KeyRole
- data Hash h a
- class (KnownNat (SizeHash h), Typeable h) ⇒ HashAlgorithm h
- newtype KeyHash (r ∷ KeyRole) = KeyHash {}
- hashKey ∷ ∀ (kd ∷ KeyRole). VKey kd → KeyHash kd
- newtype ScriptHash = ScriptHash (Hash ADDRHASH EraIndependentScript)
- data Guard ∷ KeyRole
- data EraIndependentBlockBody
- type HASH = Blake2b_256
- class SafeToHash x ⇒ HashAnnotated x i | x → i where
- hashAnnotated ∷ x → SafeHash i
- data SafeHash i
- class SafeToHash t where
- originalBytes ∷ t → ByteString
- originalBytesSize ∷ t → Int
- makeHashWithExplicitProxys ∷ Proxy i → t → SafeHash i
- type ADDRHASH = Blake2b_224
- data EraIndependentTxBody
- data EraIndependentBlockHeader
- data EraIndependentMetadata
- data EraIndependentScript
- data EraIndependentData
- data EraIndependentScriptData
- data EraIndependentTxAuxData
- data EraIndependentPParamView
- data EraIndependentScriptIntegrity
- hashTxBodySignature ∷ SignedDSIGN DSIGN (Hash HASH EraIndependentTxBody) → Hash HASH (SignedDSIGN DSIGN (Hash HASH EraIndependentTxBody))
- type DataHash = SafeHash EraIndependentData
- newtype TxAuxDataHash = TxAuxDataHash {}
- data KeyRoleVRF
- newtype VRFVerKeyHash (r ∷ KeyRoleVRF) = VRFVerKeyHash {}
- toVRFVerKeyHash ∷ ∀ v (r ∷ KeyRoleVRF). Hash HASH (VerKeyVRF v) → VRFVerKeyHash r
- fromVRFVerKeyHash ∷ ∀ (r ∷ KeyRoleVRF) v. VRFVerKeyHash r → Hash HASH (VerKeyVRF v)
- newtype HashHeader = HashHeader {}
- castSafeHash ∷ SafeHash i → SafeHash j
- extractHash ∷ SafeHash i → Hash HASH i
- standardHashSize ∷ Int
- standardAddrHashSize ∷ Int
- data StakePool ∷ KeyRole
- data StakePoolVRF ∷ KeyRoleVRF
- data GenesisRole ∷ KeyRole
- data GenesisDelegate ∷ KeyRole
- data Staking ∷ KeyRole
- data BlockIssuer ∷ KeyRole
- data DRepRole ∷ KeyRole
- data HotCommitteeRole ∷ KeyRole
- data ColdCommitteeRole ∷ KeyRole
- data GenDelegVRF ∷ KeyRoleVRF
- data BlockIssuerVRF ∷ KeyRoleVRF
- 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
- upgradeTxCert ∷ TxCert (PreviousEra era) → Either (TxCertUpgradeError era) (TxCert era)
- getVKeyWitnessTxCert ∷ TxCert era → Maybe (KeyHash 'Witness)
- getScriptWitnessTxCert ∷ TxCert era → Maybe ScriptHash
- mkRegPoolTxCert ∷ StakePoolParams → TxCert era
- getRegPoolTxCert ∷ TxCert era → Maybe StakePoolParams
- mkRetirePoolTxCert ∷ KeyHash 'StakePool → EpochNo → TxCert era
- getRetirePoolTxCert ∷ TxCert era → Maybe (KeyHash 'StakePool, EpochNo)
- lookupRegStakeTxCert ∷ TxCert era → Maybe (Credential 'Staking)
- lookupUnRegStakeTxCert ∷ TxCert era → Maybe (Credential 'Staking)
- getTotalDepositsTxCerts ∷ Foldable f ⇒ PParams era → (KeyHash 'StakePool → Bool) → f (TxCert era) → Coin
- getTotalRefundsTxCerts ∷ Foldable f ⇒ PParams era → (Credential 'Staking → Maybe Coin) → (Credential 'DRepRole → Maybe Coin) → f (TxCert era) → Coin
- type family TxCert era = (r ∷ Type) | r → era
- pattern RegPoolTxCert ∷ EraTxCert era ⇒ StakePoolParams → TxCert era
- pattern RetirePoolTxCert ∷ EraTxCert era ⇒ KeyHash 'StakePool → EpochNo → TxCert era
- data PoolCert
- = RegPool !StakePoolParams
- | RetirePool !(KeyHash 'StakePool) !EpochNo
- getPoolCertTxCert ∷ EraTxCert era ⇒ TxCert era → Maybe PoolCert
- poolCertKeyHashWitness ∷ PoolCert → KeyHash 'Witness
- isRegStakeTxCert ∷ EraTxCert era ⇒ TxCert era → Bool
- isUnRegStakeTxCert ∷ EraTxCert era ⇒ TxCert era → Bool
- type family TxCertUpgradeError era
- class (Era era, Eq (PParamsHKD Identity era), Ord (PParamsHKD Identity era), Show (PParamsHKD Identity era), NFData (PParamsHKD Identity era), NoThunks (PParamsHKD Identity era), Eq (PParamsHKD StrictMaybe era), Ord (PParamsHKD StrictMaybe era), Show (PParamsHKD StrictMaybe era), NFData (PParamsHKD StrictMaybe era), NoThunks (PParamsHKD StrictMaybe era)) ⇒ EraPParams era where
- type PParamsHKD (f ∷ Type → Type) era = (r ∷ Type) | r → era
- type UpgradePParams (f ∷ Type → Type) era
- type DowngradePParams (f ∷ Type → Type) era
- applyPPUpdates ∷ PParams era → PParamsUpdate era → PParams era
- emptyPParamsIdentity ∷ PParamsHKD Identity era
- emptyPParamsStrictMaybe ∷ PParamsHKD StrictMaybe era
- emptyUpgradePParamsUpdate ∷ UpgradePParams StrictMaybe era
- upgradePParamsHKD ∷ ∀ (f ∷ Type → Type). (HKDApplicative f, EraPParams (PreviousEra era)) ⇒ UpgradePParams f era → PParamsHKD f (PreviousEra era) → PParamsHKD f era
- downgradePParamsHKD ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, EraPParams (PreviousEra era)) ⇒ DowngradePParams f era → PParamsHKD f era → PParamsHKD f (PreviousEra era)
- hkdMinFeeAL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMinFeeBL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMaxBBSizeL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32)
- hkdMaxTxSizeL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32)
- hkdMaxBHSizeL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16)
- hkdKeyDepositL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdPoolDepositCompactL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f (CompactForm Coin))
- hkdEMaxL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f EpochInterval)
- hkdNOptL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16)
- hkdA0L ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f NonNegativeInterval)
- hkdRhoL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval)
- hkdTauL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval)
- hkdDL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval)
- ppDG ∷ SimpleGetter (PParams era) UnitInterval
- hkdExtraEntropyL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsHKD f era) (HKD f Nonce)
- hkdProtocolVersionL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Babbage" era) ⇒ Lens' (PParamsHKD f era) (HKD f ProtVer)
- ppProtocolVersionL ∷ Lens' (PParams era) ProtVer
- ppuProtocolVersionL ∷ Lens' (PParamsUpdate era) (StrictMaybe ProtVer)
- hkdMinUTxOValueL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Mary" era) ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- hkdMinPoolCostL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin)
- eraPParams ∷ [PParam era]
- newtype PParams era = PParams (PParamsHKD Identity era)
- data PParam era where
- data PParamUpdate era t = PParamUpdate {
- ppuTag ∷ Word
- ppuLens ∷ Lens' (PParamsUpdate era) (StrictMaybe t)
- emptyPParams ∷ EraPParams era ⇒ PParams era
- newtype PParamsUpdate era = PParamsUpdate (PParamsHKD StrictMaybe era)
- emptyPParamsUpdate ∷ EraPParams era ⇒ PParamsUpdate era
- genericApplyPPUpdates ∷ (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 ∷ EraPParams era ⇒ Lens' (PParams era) Coin
- ppMinFeeBL ∷ EraPParams era ⇒ Lens' (PParams era) Coin
- ppMaxBBSizeL ∷ EraPParams era ⇒ Lens' (PParams era) Word32
- ppMaxTxSizeL ∷ EraPParams era ⇒ Lens' (PParams era) Word32
- ppMaxBHSizeL ∷ EraPParams era ⇒ Lens' (PParams era) Word16
- ppKeyDepositL ∷ EraPParams era ⇒ Lens' (PParams era) Coin
- ppPoolDepositL ∷ (EraPParams era, HasCallStack) ⇒ Lens' (PParams era) Coin
- ppPoolDepositCompactL ∷ EraPParams era ⇒ Lens' (PParams era) (CompactForm Coin)
- ppEMaxL ∷ EraPParams era ⇒ Lens' (PParams era) EpochInterval
- ppNOptL ∷ EraPParams era ⇒ Lens' (PParams era) Word16
- ppA0L ∷ EraPParams era ⇒ Lens' (PParams era) NonNegativeInterval
- ppRhoL ∷ EraPParams era ⇒ Lens' (PParams era) UnitInterval
- ppTauL ∷ EraPParams era ⇒ Lens' (PParams era) UnitInterval
- ppDL ∷ (EraPParams era, AtMostEra "Alonzo" era) ⇒ Lens' (PParams era) UnitInterval
- ppExtraEntropyL ∷ (EraPParams era, AtMostEra "Alonzo" era) ⇒ Lens' (PParams era) Nonce
- ppMinUTxOValueL ∷ (EraPParams era, AtMostEra "Mary" era) ⇒ Lens' (PParams era) Coin
- ppMinPoolCostL ∷ EraPParams era ⇒ Lens' (PParams era) Coin
- ppuMinFeeAL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin)
- ppuMinFeeBL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin)
- ppuMaxBBSizeL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word32)
- ppuMaxTxSizeL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word32)
- ppuMaxBHSizeL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word16)
- ppuKeyDepositL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin)
- ppuPoolDepositL ∷ (EraPParams era, HasCallStack) ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin)
- ppuPoolDepositCompactL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe (CompactForm Coin))
- ppuEMaxL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe EpochInterval)
- ppuNOptL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word16)
- ppuA0L ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe NonNegativeInterval)
- ppuRhoL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval)
- ppuTauL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval)
- ppuDL ∷ (EraPParams era, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval)
- ppuExtraEntropyL ∷ (EraPParams era, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsUpdate era) (StrictMaybe Nonce)
- ppuMinUTxOValueL ∷ (EraPParams era, AtMostEra "Mary" era) ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin)
- ppuMinPoolCostL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin)
- ppLensHKD ∷ ∀ era f. Functor f ⇒ (PParamsHKD Identity era → f (PParamsHKD Identity era)) → PParams era → f (PParams era)
- ppuLensHKD ∷ ∀ era f. Functor f ⇒ (PParamsHKD StrictMaybe era → f (PParamsHKD StrictMaybe era)) → PParamsUpdate era → f (PParamsUpdate 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)
- type family PParamsHKD (f ∷ Type → Type) era = (r ∷ Type) | r → era
- type family UpgradePParams (f ∷ Type → Type) era
- type family DowngradePParams (f ∷ Type → Type) era
- type family PreviousEra era = (r ∷ Type) | r → era
- type family PreviousEra era = (r ∷ Type) | r → era
- type family TranslationContext era
- class (Era era, Era (PreviousEra era)) ⇒ TranslateEra era (f ∷ Type → Type) where
- type TranslationError era (f ∷ Type → Type)
- translateEra ∷ TranslationContext era → f (PreviousEra era) → Except (TranslationError era f) (f era)
- type family TranslationError era (f ∷ Type → Type)
- 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 era, ToCBOR (ti (PreviousEra era)), DecCBOR (Annotator (to era))) ⇒ Text → ti (PreviousEra era) → Except DecoderError (to era)
Transaction types
data STxTopLevel (l ∷ TxLevel) era where Source #
Constructors
| STopTxOnly ∷ ∀ era. STxTopLevel 'TopTx era |
withSTxTopLevelM ∷ ∀ (l ∷ TxLevel) era a m. (Typeable l, Era era, MonadFail m) ⇒ (STxTopLevel l era → m a) → m a Source #
data STxBothLevels (l ∷ TxLevel) era where Source #
Constructors
| STopTx ∷ ∀ era. STxBothLevels 'TopTx era | |
| SSubTx ∷ ∀ era. STxBothLevels 'SubTx era |
withSTxBothLevels ∷ ∀ (l ∷ TxLevel) era a. (Typeable l, HasCallStack) ⇒ (STxBothLevels l era → a) → a Source #
class Era era ⇒ EraTxLevel era Source #
Associated Types
type STxLevel (l ∷ TxLevel) era = (r ∷ Type) | r → era Source #
Supported transaction level as a singleton. One of these two should be used:
STxTopLevel- for eras up to and including Conway, that do not support nested transactions.STxBothLevels- for Dijkstra onwards that do support nested transactions.
type STxLevel (l ∷ TxLevel) era = STxBothLevels l era
class EraTxLevel era ⇒ HasEraTxLevel (t ∷ TxLevel → Type → Type) era where Source #
Type class for data families that have different definition depending on the level. Currently
it is only Tx and TxBody that have this distinction.
Methods
toSTxLevel ∷ ∀ (l ∷ TxLevel). t l era → STxLevel l era Source #
asSTxTopLevel ∷ ∀ (l ∷ TxLevel) t era. (Typeable l, HasEraTxLevel t era, STxLevel l era ~ STxTopLevel l era) ⇒ t 'TopTx era → t l era Source #
mkSTxTopLevelM ∷ ∀ (l ∷ TxLevel) t m era. (Typeable l, Monad m, HasEraTxLevel t era, STxLevel l era ~ STxTopLevel l era) ⇒ m (t 'TopTx era) → m (t l era) Source #
withTopTxLevelOnly ∷ ∀ t era (l ∷ TxLevel) a. (HasEraTxLevel t era, STxLevel l era ~ STxTopLevel l era) ⇒ t l era → (t 'TopTx era → a) → a Source #
asSTxBothLevels ∷ ∀ (l ∷ TxLevel) t era. (Typeable l, HasEraTxLevel t era, STxLevel l era ~ STxBothLevels l era) ⇒ t 'TopTx era → t 'SubTx era → t l era Source #
mkSTxBothLevelsM ∷ ∀ (l ∷ TxLevel) t m era. (Typeable l, Monad m, HasEraTxLevel t era, STxLevel l era ~ STxBothLevels l era) ⇒ m (t 'TopTx era) → m (t 'SubTx era) → m (t l era) Source #
withBothTxLevels ∷ ∀ t era (l ∷ TxLevel) a. (HasEraTxLevel t era, STxLevel l era ~ STxBothLevels l era) ⇒ t l era → (t 'TopTx era → a) → (t 'SubTx era → a) → a Source #
type family STxLevel (l ∷ TxLevel) era = (r ∷ Type) | r → era Source #
Supported transaction level as a singleton. One of these two should be used:
STxTopLevel- for eras up to and including Conway, that do not support nested transactions.STxBothLevels- for Dijkstra onwards that do support nested transactions.
Era-changing types
class (EraTxBody era, EraTxWits era, EraTxAuxData era, EraPParams era, HasEraTxLevel Tx era, ∀ (l ∷ TxLevel). Typeable l ⇒ NoThunks (Tx l era), ∀ (l ∷ TxLevel). Typeable l ⇒ DecCBOR (Annotator (Tx l era)), ∀ (l ∷ TxLevel). Typeable l ⇒ ToCBOR (Tx l era), ∀ (l ∷ TxLevel). EncCBOR (Tx l era), ∀ (l ∷ TxLevel). NFData (Tx l era), ∀ (l ∷ TxLevel). Show (Tx l era), ∀ (l ∷ TxLevel). Eq (Tx l era)) ⇒ EraTx era where Source #
A transaction.
Minimal complete definition
mkBasicTx, bodyTxL, witsTxL, auxDataTxL, sizeTxF, validateNativeScript, getMinFeeTx
Methods
mkBasicTx ∷ ∀ (l ∷ TxLevel). TxBody l era → Tx l era Source #
bodyTxL ∷ ∀ (l ∷ TxLevel). Lens' (Tx l era) (TxBody l era) Source #
witsTxL ∷ ∀ (l ∷ TxLevel). Lens' (Tx l era) (TxWits era) Source #
auxDataTxL ∷ ∀ (l ∷ TxLevel). Lens' (Tx l era) (StrictMaybe (TxAuxData era)) Source #
sizeTxF ∷ ∀ (l ∷ TxLevel). HasCallStack ⇒ SimpleGetter (Tx l era) Word32 Source #
For fee calculation and estimations of impact on block space
sizeTxForFeeCalculation ∷ ∀ (l ∷ TxLevel). (HasCallStack, SafeToHash (TxWits era), Typeable l) ⇒ Tx l era → Word32 Source #
For fee calculation and estimations of impact on block space
To replace sizeTxF after it has been proved equivalent to it .
validateNativeScript ∷ ∀ (l ∷ TxLevel). Tx l era → NativeScript era → Bool Source #
Using information from the transaction validate the supplied native script.
Arguments
| ∷ ∀ (l ∷ TxLevel). PParams era | |
| → Tx l era | |
| → Int | Size in bytes of reference scripts present in this transaction |
| → Coin |
Minimum fee calculation excluding witnesses
class (Val (Value era), ToJSON (TxOut era), DecCBOR (Value era), DecCBOR (CompactForm (Value era)), MemPack (CompactForm (Value era)), EncCBOR (Value era), ToCBOR (TxOut era), EncCBOR (TxOut era), DecCBOR (TxOut era), DecShareCBOR (TxOut era), Share (TxOut era) ~ Interns (Credential 'Staking), NoThunks (TxOut era), NFData (TxOut era), Show (TxOut era), Eq (TxOut era), MemPack (TxOut era), EraPParams era) ⇒ EraTxOut era where Source #
Abstract interface into specific fields of a TxOut
Minimal complete definition
mkBasicTxOut, upgradeTxOut, valueEitherTxOutL, addrEitherTxOutL, (getMinCoinSizedTxOut | getMinCoinTxOut)
Associated Types
type TxOut era = (r ∷ Type) | r → era Source #
The output of a UTxO for a particular era
Methods
mkBasicTxOut ∷ Addr → Value era → TxOut era Source #
upgradeTxOut ∷ 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 ∷ 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 Source #
compactAddrTxOutL ∷ Lens' (TxOut era) CompactAddr Source #
addrEitherTxOutL ∷ Lens' (TxOut era) (Either Addr CompactAddr) 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) 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, HasEraTxLevel TxBody era, ∀ (l ∷ TxLevel). HashAnnotated (TxBody l era) EraIndependentTxBody, ∀ (l ∷ TxLevel). EncCBOR (TxBody l era), ∀ (l ∷ TxLevel). Typeable l ⇒ DecCBOR (Annotator (TxBody l era)), ∀ (l ∷ TxLevel). Typeable l ⇒ ToCBOR (TxBody l era), ∀ (l ∷ TxLevel). Typeable l ⇒ NoThunks (TxBody l era), ∀ (l ∷ TxLevel). NFData (TxBody l era), ∀ (l ∷ TxLevel). Show (TxBody l era), ∀ (l ∷ TxLevel). Eq (TxBody l era), ∀ (l ∷ TxLevel). EqRaw (TxBody l era)) ⇒ EraTxBody era where Source #
Minimal complete definition
mkBasicTxBody, inputsTxBodyL, outputsTxBodyL, feeTxBodyL, withdrawalsTxBodyL, auxDataHashTxBodyL, spendableInputsTxBodyF, allInputsTxBodyF, certsTxBodyL
Methods
mkBasicTxBody ∷ ∀ (l ∷ TxLevel). Typeable l ⇒ TxBody l era Source #
inputsTxBodyL ∷ ∀ (l ∷ TxLevel). Lens' (TxBody l era) (Set TxIn) Source #
outputsTxBodyL ∷ ∀ (l ∷ TxLevel). Lens' (TxBody l era) (StrictSeq (TxOut era)) Source #
feeTxBodyL ∷ Lens' (TxBody 'TopTx era) Coin Source #
withdrawalsTxBodyL ∷ ∀ (l ∷ TxLevel). Lens' (TxBody l era) Withdrawals Source #
auxDataHashTxBodyL ∷ ∀ (l ∷ TxLevel). Lens' (TxBody l era) (StrictMaybe TxAuxDataHash) Source #
spendableInputsTxBodyF ∷ ∀ (l ∷ TxLevel). SimpleGetter (TxBody l era) (Set TxIn) 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 'TopTx era) (Set TxIn) 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 ∷ ∀ (l ∷ TxLevel). Lens' (TxBody l era) (StrictSeq (TxCert era)) Source #
getTotalDepositsTxBody Source #
Arguments
| ∷ ∀ (l ∷ TxLevel). PParams era | |
| → (KeyHash 'StakePool → Bool) | Check whether stake pool is registered or not |
| → TxBody l 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 #
Arguments
| ∷ ∀ (l ∷ TxLevel). PParams era | |
| → (Credential 'Staking → Maybe Coin) | Lookup current deposit for Staking credential if one is registered |
| → (Credential 'DRepRole → Maybe Coin) | Lookup current deposit for DRep credential if one is registered |
| → TxBody l 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 'TopTx 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.
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) ⇒ EraTxAuxData era where Source #
TxAuxData which may be attached to a transaction
hashTxAuxData ∷ EraTxAuxData era ⇒ TxAuxData era → TxAuxDataHash Source #
Compute a hash of TxAuxData
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
Minimal complete definition
Methods
mkBasicTxWits ∷ TxWits era Source #
addrTxWitsL ∷ Lens' (TxWits era) (Set (WitVKey 'Witness)) Source #
bootAddrTxWitsL ∷ Lens' (TxWits era) (Set BootstrapWitness) Source #
scriptTxWitsL ∷ Lens' (TxWits era) (Map ScriptHash (Script 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), ToCBOR (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.
Associated Types
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 #
Methods
upgradeScript ∷ 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. If you need to retain underlying bytes then you can use translateEraThroughCBOR
scriptPrefixTag ∷ Script era → ByteString Source #
getNativeScript ∷ Script era → Maybe (NativeScript era) Source #
fromNativeScript ∷ NativeScript era → Script era Source #
hashScript ∷ EraScript era ⇒ Script era → ScriptHash Source #
Compute ScriptHash of a Script for a particular era.
hashScriptTxWitsL ∷ EraTxWits era ⇒ Lens (TxWits era) (TxWits era) (Map ScriptHash (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), NoThunks (PParamsHKD Identity era), Eq (PParamsHKD StrictMaybe era), Ord (PParamsHKD StrictMaybe era), Show (PParamsHKD StrictMaybe era), NFData (PParamsHKD StrictMaybe era), NoThunks (PParamsHKD StrictMaybe era)) ⇒ EraPParams era where Source #
Minimal complete definition
emptyPParamsIdentity, emptyPParamsStrictMaybe, upgradePParamsHKD, downgradePParamsHKD, hkdMinFeeAL, hkdMinFeeBL, hkdMaxBBSizeL, hkdMaxTxSizeL, hkdMaxBHSizeL, hkdKeyDepositL, hkdPoolDepositCompactL, hkdEMaxL, hkdNOptL, hkdA0L, hkdRhoL, hkdTauL, hkdDL, hkdExtraEntropyL, hkdProtocolVersionL, hkdMinUTxOValueL, hkdMinPoolCostL, eraPParams
Associated Types
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 Source #
type DowngradePParams (f ∷ Type → Type) era Source #
Methods
applyPPUpdates ∷ PParams era → PParamsUpdate era → PParams era Source #
Applies a protocol parameters update
default applyPPUpdates ∷ (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 #
emptyUpgradePParamsUpdate ∷ UpgradePParams StrictMaybe era Source #
default emptyUpgradePParamsUpdate ∷ UpgradePParams StrictMaybe era ~ () ⇒ UpgradePParams StrictMaybe era Source #
upgradePParamsHKD ∷ ∀ (f ∷ Type → Type). (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 ∷ ∀ (f ∷ Type → Type). (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 ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The linear factor for the minimum fee calculation
hkdMinFeeBL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The constant factor for the minimum fee calculation
hkdMaxBBSizeL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32) Source #
Maximal block body size
hkdMaxTxSizeL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32) Source #
Maximal transaction size
hkdMaxBHSizeL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16) Source #
Maximal block header size
hkdKeyDepositL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The amount of a key registration deposit
hkdPoolDepositCompactL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f (CompactForm Coin)) Source #
The amount of a pool registration deposit
hkdEMaxL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f EpochInterval) Source #
epoch bound on pool retirement
hkdNOptL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16) Source #
Desired number of pools
hkdA0L ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f NonNegativeInterval) Source #
Pool influence
hkdRhoL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Monetary expansion
hkdTauL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Treasury expansion
hkdDL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Decentralization parameter
ppDG ∷ SimpleGetter (PParams era) UnitInterval Source #
Decentralization parameter getter
default ppDG ∷ AtMostEra "Alonzo" era ⇒ SimpleGetter (PParams era) UnitInterval Source #
hkdExtraEntropyL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsHKD f era) (HKD f Nonce) Source #
Extra entropy
hkdProtocolVersionL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Babbage" era) ⇒ Lens' (PParamsHKD f era) (HKD f ProtVer) Source #
Protocol version
ppProtocolVersionL ∷ Lens' (PParams era) ProtVer Source #
ppuProtocolVersionL ∷ Lens' (PParamsUpdate era) (StrictMaybe ProtVer) Source #
PParamsUpdate Protocol version
hkdMinUTxOValueL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Mary" era) ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
Minimum UTxO value
hkdMinPoolCostL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
Minimum Stake Pool Cost
eraPParams ∷ [PParam era] Source #
wireSizeTxF ∷ ∀ era (l ∷ TxLevel). EraTx era ⇒ SimpleGetter (Tx l era) Word32 Source #
txsize computes the length of the serialised bytes (actual size)
binaryUpgradeTx ∷ ∀ era (l ∷ TxLevel). (Era era, ToCBOR (Tx l (PreviousEra era)), DecCBOR (Annotator (Tx l era))) ⇒ Tx l (PreviousEra era) → Except DecoderError (Tx l era) Source #
Translate a transaction through its binary representation from previous to current era.
binaryUpgradeTxBody ∷ ∀ era (l ∷ TxLevel). (Era era, ToCBOR (TxBody l (PreviousEra era)), DecCBOR (Annotator (TxBody l era))) ⇒ TxBody l (PreviousEra era) → Except DecoderError (TxBody l era) Source #
Translate a tx body through its binary representation from previous to current era.
binaryUpgradeTxWits ∷ (Era era, ToCBOR (TxWits (PreviousEra era)), DecCBOR (Annotator (TxWits era))) ⇒ TxWits (PreviousEra era) → Except DecoderError (TxWits era) Source #
Translate tx witnesses through its binary representation from previous to current era.
binaryUpgradeTxAuxData ∷ (Era era, ToCBOR (TxAuxData (PreviousEra era)), DecCBOR (Annotator (TxAuxData era))) ⇒ TxAuxData (PreviousEra era) → Except DecoderError (TxAuxData era) Source #
Translate tx auxData through its binary representation from previous to current era.
fromStrictMaybeL ∷ ∀ a f. Functor f ⇒ (Maybe a → f (Maybe a)) → StrictMaybe a → f (StrictMaybe a) Source #
toStrictMaybeL ∷ ∀ a f. Functor f ⇒ (StrictMaybe a → f (StrictMaybe a)) → Maybe a → f (Maybe a) Source #
Era
This is the era that preceded Shelley era. It cannot have any other class instances,
except for Era type class.
Instances
| Era ByronEra | |||||||||||||||||
Defined in Cardano.Ledger.Internal.Definition.Era Associated Types
| |||||||||||||||||
| type EraName ByronEra | |||||||||||||||||
Defined in Cardano.Ledger.Internal.Definition.Era | |||||||||||||||||
| type PreviousEra ByronEra | |||||||||||||||||
Defined in Cardano.Ledger.Internal.Definition.Era | |||||||||||||||||
| type ProtVerHigh ByronEra | |||||||||||||||||
Defined in Cardano.Ledger.Internal.Definition.Era | |||||||||||||||||
| type ProtVerLow ByronEra | |||||||||||||||||
Defined in Cardano.Ledger.Internal.Definition.Era | |||||||||||||||||
class (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) ⇒ Era era where Source #
Minimal complete definition
Nothing
Associated Types
type EraName era ∷ Symbol Source #
type PreviousEra era = (r ∷ Type) | r → era Source #
Map an era to its predecessor.
For example:
type instance PreviousEra AllegraEra = ShelleyEra
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
Methods
Textual name of the current era.
Designed to be used with TypeApplications:
>>>eraName @ByronEra"Byron"
Instances
type family EraName era ∷ Symbol Source #
Instances
| type EraName AllegraEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type EraName AlonzoEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type EraName BabbageEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type EraName ByronEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type EraName ConwayEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type EraName DijkstraEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type EraName MaryEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type EraName ShelleyEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
type family PreviousEra era = (r ∷ Type) | r → era Source #
Map an era to its predecessor.
For example:
type instance PreviousEra AllegraEra = ShelleyEra
Instances
| type PreviousEra AllegraEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra AlonzoEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra BabbageEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra ByronEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra ConwayEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra DijkstraEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra MaryEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra ShelleyEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
type family ProtVerLow era ∷ Nat Source #
Lowest major protocol version for this era
Instances
| type ProtVerLow AllegraEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerLow AlonzoEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerLow BabbageEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerLow ByronEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerLow ConwayEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerLow DijkstraEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerLow MaryEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerLow ShelleyEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
type family ProtVerHigh era ∷ Nat Source #
Highest major protocol version for this era. By default se to ProtVerLow
Instances
| type ProtVerHigh AllegraEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerHigh AlonzoEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerHigh BabbageEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerHigh ByronEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerHigh ConwayEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerHigh DijkstraEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerHigh MaryEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type ProtVerHigh ShelleyEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
eraProtVerLow ∷ Era era ⇒ Version Source #
Get the value level Version of the lowest major protocol version for the supplied era.
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
| (KnownSymbol rule, Era era) ⇒ FromCBOR (VoidEraRule rule era) Source # | |
Defined in Cardano.Ledger.Core.Era | |
| (KnownSymbol rule, Era era) ⇒ ToCBOR (VoidEraRule rule era) Source # | |
Defined in Cardano.Ledger.Core.Era Methods toCBOR ∷ VoidEraRule rule era → Encoding Source # encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (VoidEraRule rule era) → Size Source # encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [VoidEraRule rule era] → Size Source # | |
| (KnownSymbol rule, Era era) ⇒ DecCBOR (VoidEraRule rule era) Source # | |
Defined in Cardano.Ledger.Core.Era | |
| (KnownSymbol rule, Era era) ⇒ EncCBOR (VoidEraRule rule era) Source # | |
Defined in Cardano.Ledger.Core.Era Methods encCBOR ∷ VoidEraRule rule era → Encoding Source # | |
| NFData (VoidEraRule rule era) Source # | |
Defined in Cardano.Ledger.Core.Era Methods rnf ∷ VoidEraRule rule era → () # | |
| Show (VoidEraRule rule era) Source # | |
Defined in Cardano.Ledger.Core.Era Methods showsPrec ∷ Int → VoidEraRule rule era → ShowS # show ∷ VoidEraRule rule era → String # showList ∷ [VoidEraRule rule era] → ShowS # | |
| Eq (VoidEraRule rule era) Source # | |
Defined in Cardano.Ledger.Core.Era Methods (==) ∷ VoidEraRule rule era → VoidEraRule rule era → Bool # (/=) ∷ VoidEraRule rule era → VoidEraRule rule era → Bool # | |
| Ord (VoidEraRule rule era) Source # | |
Defined in Cardano.Ledger.Core.Era Methods compare ∷ VoidEraRule rule era → VoidEraRule rule era → Ordering # (<) ∷ VoidEraRule rule era → VoidEraRule rule era → Bool # (<=) ∷ VoidEraRule rule era → VoidEraRule rule era → Bool # (>) ∷ VoidEraRule rule era → VoidEraRule rule era → Bool # (>=) ∷ VoidEraRule rule era → VoidEraRule rule era → Bool # max ∷ VoidEraRule rule era → VoidEraRule rule era → VoidEraRule rule era # min ∷ VoidEraRule rule era → VoidEraRule rule era → VoidEraRule rule era # | |
absurdEraRule ∷ ∀ (rule ∷ Symbol) era a. VoidEraRule rule era → a Source #
class EraRuleFailure rule era ~ PredicateFailure (EraRule rule era) ⇒ InjectRuleFailure (rule ∷ Symbol) (t ∷ Type → Type) era where Source #
Minimal complete definition
Nothing
Methods
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 ∷ Type → Type) era where Source #
Minimal complete definition
Nothing
Methods
injectEvent ∷ t era → EraRuleEvent rule era Source #
default injectEvent ∷ t era ~ EraRuleEvent rule era ⇒ t era → EraRuleEvent rule era Source #
type AtMostEra (eraMostEra ∷ Symbol) era = ProtVerAtMost era (ProtVerHigh (EraFromName eraMostEra)) Source #
Restrict the era to equal to eraName or come before it.
type AtLeastEra (atLeastEra ∷ Symbol) era = ProtVerAtLeast era (ProtVerLow (EraFromName atLeastEra)) Source #
Restrict the era to equal to atLeastEra or come after it
type ExactEra inEra era = ProtVerInBounds era (ProtVerLow inEra) (ProtVerHigh inEra) 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) where ... Source #
Requirement for the era's lowest protocol version to be lower or equal to the supplied value
Equations
| ProtVerAtMost era h = ProtVerIsInBounds "at most" era h (ProtVerLow era <=? h) |
type family ProtVerAtLeast era (l ∷ Nat) where ... Source #
Requirement for the era's highest protocol version to be higher or equal to the supplied value
Equations
| ProtVerAtLeast era l = ProtVerIsInBounds "at least" era l (l <=? ProtVerHigh era) |
type ProtVerInBounds era (l ∷ Nat) (h ∷ Nat) = (ProtVerAtLeast era l, ProtVerAtMost era h) Source #
Restrict a lower and upper bounds of the protocol version for the particular era
atLeastEra ∷ ∀ (eraName ∷ Symbol) era. 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 @"Babbage" @ConwayEra atLeastEra @"Babbage" @BabbageEra
However this will result in a type error
atLeastEra @"Babbage" @AlonzoEra
atMostEra ∷ ∀ (eraName ∷ Symbol) era. 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 atMostEra @AlonzoEra @MaryEra
However this will result in a type error
atMostEra @BabbageEra @ConwayEra
notSupportedInThisEraL ∷ HasCallStack ⇒ Lens' a b Source #
eraProtVerHigh ∷ Era era ⇒ Version Source #
Get the value level Version of the highest major protocol version for the supplied era.
eraProtVersions ∷ Era era ⇒ [Version] Source #
List with all major versions that are used in the particular era.
fromEraCBOR ∷ (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 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
eraDecoderWithBytes instead.
eraDecoderWithBytes ∷ ∀ era t s. Era era ⇒ ByteString → Decoder s t → Decoder s t Source #
Just like eraDecoder, but for decoders that rely on access for underlying bytes
- EraBlockBody
The idea of EraBlockBody 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 BlockBody, 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 (BlockBody era), Show (BlockBody era), Typeable (BlockBody era), EncCBORGroup (BlockBody era), DecCBOR (Annotator (BlockBody era))) ⇒ EraBlockBody era where Source #
Indicates that an era supports segregated witnessing.
This class embodies an isomorphism between 'BlockBody era' and 'StrictSeq
(Tx l era)', witnessed by the txSeqBlockBodyL lens.
Methods
mkBasicBlockBody ∷ BlockBody era Source #
txSeqBlockBodyL ∷ Lens' (BlockBody era) (StrictSeq (Tx 'TopTx era)) Source #
hashBlockBody ∷ BlockBody era → Hash HASH EraIndependentBlockBody Source #
Get the block body hash from the BlockBody. 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.
Constructors
| MemberReward | |
| LeaderReward |
Instances
| ToJSON RewardType Source # | |||||
Defined in Cardano.Ledger.Rewards Methods toJSON ∷ RewardType → Value Source # toEncoding ∷ RewardType → Encoding Source # toJSONList ∷ [RewardType] → Value Source # toEncodingList ∷ [RewardType] → Encoding Source # omitField ∷ RewardType → Bool Source # | |||||
| DecCBOR RewardType Source # | |||||
Defined in Cardano.Ledger.Rewards | |||||
| EncCBOR RewardType Source # | |||||
Defined in Cardano.Ledger.Rewards Methods encCBOR ∷ RewardType → Encoding Source # | |||||
| NFData RewardType Source # | |||||
Defined in Cardano.Ledger.Rewards Methods rnf ∷ RewardType → () # | |||||
| Bounded RewardType Source # | |||||
Defined in Cardano.Ledger.Rewards | |||||
| Enum RewardType Source # | |||||
Defined in Cardano.Ledger.Rewards Methods succ ∷ RewardType → RewardType # pred ∷ RewardType → RewardType # toEnum ∷ Int → RewardType # fromEnum ∷ RewardType → Int # enumFrom ∷ RewardType → [RewardType] # enumFromThen ∷ RewardType → RewardType → [RewardType] # enumFromTo ∷ RewardType → RewardType → [RewardType] # enumFromThenTo ∷ RewardType → RewardType → RewardType → [RewardType] # | |||||
| Generic RewardType Source # | |||||
Defined in Cardano.Ledger.Rewards Associated Types
| |||||
| Show RewardType Source # | |||||
Defined in Cardano.Ledger.Rewards Methods showsPrec ∷ Int → RewardType → ShowS # show ∷ RewardType → String # showList ∷ [RewardType] → ShowS # | |||||
| Eq RewardType Source # | |||||
Defined in Cardano.Ledger.Rewards | |||||
| Ord RewardType Source # | |||||
Defined in Cardano.Ledger.Rewards Methods compare ∷ RewardType → RewardType → Ordering # (<) ∷ RewardType → RewardType → Bool # (<=) ∷ RewardType → RewardType → Bool # (>) ∷ RewardType → RewardType → Bool # (>=) ∷ RewardType → RewardType → Bool # max ∷ RewardType → RewardType → RewardType # min ∷ RewardType → RewardType → RewardType # | |||||
| NoThunks RewardType Source # | |||||
Defined in Cardano.Ledger.Rewards | |||||
| type Rep RewardType Source # | |||||
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
Constructors
| Reward | |
Fields
| |
Instances
| ToJSON Reward Source # | |||||
| DecCBOR Reward Source # | |||||
| EncCBOR Reward Source # | |||||
| ToKeyValuePairs Reward Source # | |||||
Defined in Cardano.Ledger.Rewards Methods toKeyValuePairs ∷ KeyValue e kv ⇒ Reward → [kv] Source # | |||||
| NFData Reward Source # | |||||
Defined in Cardano.Ledger.Rewards | |||||
| Generic Reward Source # | |||||
Defined in Cardano.Ledger.Rewards Associated Types
| |||||
| Show Reward Source # | |||||
| Eq Reward Source # | |||||
| Ord Reward Source # | Note that this Ord instance is chosen to align precisely
with the Allegra reward aggregation, as given by the
function | ||||
| NoThunks Reward Source # | |||||
| type Rep Reward Source # | |||||
Defined in Cardano.Ledger.Rewards type Rep Reward = D1 ('MetaData "Reward" "Cardano.Ledger.Rewards" "cardano-ledger-core-1.19.0.0-inplace" 'False) (C1 ('MetaCons "Reward" 'PrefixI 'True) (S1 ('MetaSel ('Just "rewardType") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 RewardType) :*: (S1 ('MetaSel ('Just "rewardPool") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool)) :*: S1 ('MetaSel ('Just "rewardAmount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin)))) | |||||
Re-exports
The role of a key.
All key roles are fixed and unique, except for the Witness role. In particular,
keys can be cast to a Witness role with the help of asWitness, because same witness
can be valid for many roles.
In fact, it is perfectly allowable for a key to be used in many roles by the end user; there is nothing prohibiting somebody using the same underlying key or a script as their payment and staking credential, as well as the key for their stake pool. However, in the ledger code mixing up keys with different roles could be catastrophic, that is why we have this separation.
Instances
| HashAlgorithm h ⇒ IsString (Q (TExp (Hash h a))) | This instance is meant to be used with
| ||||
Defined in Cardano.Crypto.Hash.Class | |||||
| HashAlgorithm h ⇒ FromJSON (Hash h a) | |||||
| HashAlgorithm h ⇒ FromJSONKey (Hash h a) | |||||
Defined in Cardano.Crypto.Hash.Class Methods fromJSONKey ∷ FromJSONKeyFunction (Hash h a) Source # fromJSONKeyList ∷ FromJSONKeyFunction [Hash h a] Source # | |||||
| HashAlgorithm h ⇒ ToJSON (Hash h a) | |||||
| HashAlgorithm h ⇒ ToJSONKey (Hash h a) | |||||
Defined in Cardano.Crypto.Hash.Class Methods toJSONKey ∷ ToJSONKeyFunction (Hash h a) Source # toJSONKeyList ∷ ToJSONKeyFunction [Hash h a] Source # | |||||
| (HashAlgorithm h, Typeable a) ⇒ FromCBOR (Hash h a) | |||||
| (HashAlgorithm h, Typeable a) ⇒ ToCBOR (Hash h a) | |||||
| SignableRepresentation (Hash a b) Source # | |||||
Defined in Cardano.Ledger.Orphans Methods getSignableRepresentation ∷ Hash a b → ByteString Source # | |||||
| (HashAlgorithm h, Typeable a) ⇒ DecCBOR (Hash h a) | |||||
| HashAlgorithm h ⇒ EncCBOR (Hash h a) | |||||
| HashAlgorithm h ⇒ SafeToHash (Hash h i) Source # | Hash of a hash. Hash is always safe to hash. Do you even hash? | ||||
Defined in Cardano.Ledger.Hashes Methods originalBytes ∷ Hash h i → ByteString Source # originalBytesSize ∷ Hash h i → Int Source # makeHashWithExplicitProxys ∷ Proxy i0 → Hash h i → SafeHash i0 Source # | |||||
| HashAlgorithm h ⇒ Default (Hash h b) Source # | |||||
Defined in Cardano.Ledger.Orphans | |||||
| NFData (Hash h a) | |||||
Defined in Cardano.Crypto.Hash.Class | |||||
| HashAlgorithm h ⇒ IsString (Hash h a) | |||||
Defined in Cardano.Crypto.Hash.Class Methods fromString ∷ String → Hash h a # | |||||
| Generic (Hash h a) | |||||
Defined in Cardano.Crypto.Hash.Class Associated Types
| |||||
| HashAlgorithm h ⇒ Read (Hash h a) | |||||
| Show (Hash h a) | |||||
| Eq (Hash h a) | |||||
| Ord (Hash h a) | |||||
Defined in Cardano.Crypto.Hash.Class | |||||
| HeapWords (Hash h a) | |||||
| HashAlgorithm h ⇒ MemPack (Hash h a) | |||||
| NoThunks (Hash h a) | |||||
| HashAlgorithm h ⇒ IsString (Code Q (Hash h a)) | |||||
Defined in Cardano.Crypto.Hash.Class | |||||
| type Rep (Hash h a) | |||||
Defined in Cardano.Crypto.Hash.Class type Rep (Hash h a) = D1 ('MetaData "Hash" "Cardano.Crypto.Hash.Class" "cardano-crypto-class-2.2.3.1-93e2c82f664404a263ce0cfe72acde6cccce29dd72e7a756ec140c9b1d091d59" 'True) (C1 ('MetaCons "UnsafeHashRep" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PackedBytes (SizeHash h))))) | |||||
class (KnownNat (SizeHash h), Typeable h) ⇒ HashAlgorithm h Source #
Minimal complete definition
Instances
| HashAlgorithm Blake2b_224 | |||||
Defined in Cardano.Crypto.Hash.Blake2b Associated Types
Methods hashAlgorithmName ∷ proxy Blake2b_224 → String Source # digest ∷ proxy Blake2b_224 → ByteString → ByteString Source # | |||||
| HashAlgorithm Blake2b_256 | |||||
Defined in Cardano.Crypto.Hash.Blake2b Associated Types
Methods hashAlgorithmName ∷ proxy Blake2b_256 → String Source # digest ∷ proxy Blake2b_256 → ByteString → ByteString Source # | |||||
| HashAlgorithm Keccak256 | |||||
Defined in Cardano.Crypto.Hash.Keccak256 Associated Types
Methods hashAlgorithmName ∷ proxy Keccak256 → String Source # digest ∷ proxy Keccak256 → ByteString → ByteString Source # | |||||
| HashAlgorithm NeverHash | |||||
Defined in Cardano.Crypto.Hash.NeverUsed Associated Types
Methods hashAlgorithmName ∷ proxy NeverHash → String Source # digest ∷ proxy NeverHash → ByteString → ByteString Source # | |||||
| HashAlgorithm RIPEMD160 | |||||
Defined in Cardano.Crypto.Hash.RIPEMD160 Associated Types
Methods hashAlgorithmName ∷ proxy RIPEMD160 → String Source # digest ∷ proxy RIPEMD160 → ByteString → ByteString Source # | |||||
| HashAlgorithm SHA256 | |||||
Defined in Cardano.Crypto.Hash.SHA256 Associated Types
Methods hashAlgorithmName ∷ proxy SHA256 → String Source # digest ∷ proxy SHA256 → ByteString → ByteString Source # | |||||
| HashAlgorithm SHA3_256 | |||||
Defined in Cardano.Crypto.Hash.SHA3_256 Associated Types
Methods hashAlgorithmName ∷ proxy SHA3_256 → String Source # digest ∷ proxy SHA3_256 → ByteString → ByteString Source # | |||||
| HashAlgorithm SHA3_512 | |||||
Defined in Cardano.Crypto.Hash.SHA3_512 Associated Types
Methods hashAlgorithmName ∷ proxy SHA3_512 → String Source # digest ∷ proxy SHA3_512 → ByteString → ByteString Source # | |||||
| HashAlgorithm SHA512 | |||||
Defined in Cardano.Crypto.Hash.SHA512 Associated Types
Methods hashAlgorithmName ∷ proxy SHA512 → String Source # digest ∷ proxy SHA512 → ByteString → ByteString Source # | |||||
| (KnownNat n, CmpNat n 33 ~ 'LT) ⇒ HashAlgorithm (Blake2bPrefix n) | |||||
Defined in Cardano.Crypto.Hash.Short Associated Types
Methods hashAlgorithmName ∷ proxy (Blake2bPrefix n) → String Source # digest ∷ proxy (Blake2bPrefix n) → ByteString → ByteString Source # | |||||
newtype KeyHash (r ∷ KeyRole) Source #
Discriminated hash of public Key
Instances
| HasKeyRole KeyHash Source # | |
Defined in Cardano.Ledger.Hashes | |
| FromJSON (KeyHash r) Source # | |
| FromJSONKey (KeyHash r) Source # | |
Defined in Cardano.Ledger.Hashes Methods | |
| ToJSON (KeyHash r) Source # | |
| ToJSONKey (KeyHash r) Source # | |
Defined in Cardano.Ledger.Hashes Methods toJSONKey ∷ ToJSONKeyFunction (KeyHash r) Source # | |
| Typeable r ⇒ FromCBOR (KeyHash r) Source # | |
| Typeable r ⇒ ToCBOR (KeyHash r) Source # | |
| Typeable r ⇒ DecCBOR (KeyHash r) Source # | |
| EncCBOR (KeyHash r) Source # | |
| Default (KeyHash r) Source # | |
Defined in Cardano.Ledger.Hashes | |
| NFData (KeyHash r) Source # | |
Defined in Cardano.Ledger.Hashes | |
| Generic (KeyHash r) Source # | |
| Show (KeyHash r) Source # | |
| Eq (KeyHash r) Source # | |
| Ord (KeyHash r) Source # | |
Defined in Cardano.Ledger.Hashes | |
| MemPack (KeyHash r) Source # | |
| NoThunks (KeyHash r) Source # | |
| type Rep (KeyHash r) Source # | |
Defined in Cardano.Ledger.Hashes | |
newtype ScriptHash Source #
Constructors
| ScriptHash (Hash ADDRHASH EraIndependentScript) |
Instances
| FromJSON ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes Methods parseJSON ∷ Value → Parser ScriptHash Source # parseJSONList ∷ Value → Parser [ScriptHash] Source # | |||||
| FromJSONKey ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| ToJSON ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes Methods toJSON ∷ ScriptHash → Value Source # toEncoding ∷ ScriptHash → Encoding Source # toJSONList ∷ [ScriptHash] → Value Source # toEncodingList ∷ [ScriptHash] → Encoding Source # omitField ∷ ScriptHash → Bool Source # | |||||
| ToJSONKey ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| FromCBOR ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| ToCBOR ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes Methods toCBOR ∷ ScriptHash → Encoding Source # encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy ScriptHash → Size Source # encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [ScriptHash] → Size Source # | |||||
| DecCBOR ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| EncCBOR ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes Methods encCBOR ∷ ScriptHash → Encoding Source # | |||||
| NFData ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes Methods rnf ∷ ScriptHash → () # | |||||
| Generic ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes Associated Types
| |||||
| Show ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes Methods showsPrec ∷ Int → ScriptHash → ShowS # show ∷ ScriptHash → String # showList ∷ [ScriptHash] → ShowS # | |||||
| Eq ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| Ord ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes Methods compare ∷ ScriptHash → ScriptHash → Ordering # (<) ∷ ScriptHash → ScriptHash → Bool # (<=) ∷ ScriptHash → ScriptHash → Bool # (>) ∷ ScriptHash → ScriptHash → Bool # (>=) ∷ ScriptHash → ScriptHash → Bool # max ∷ ScriptHash → ScriptHash → ScriptHash # min ∷ ScriptHash → ScriptHash → ScriptHash # | |||||
| MemPack ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| NoThunks ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| type Rep ScriptHash Source # | |||||
Defined in Cardano.Ledger.Hashes type Rep ScriptHash = D1 ('MetaData "ScriptHash" "Cardano.Ledger.Hashes" "cardano-ledger-core-1.19.0.0-inplace" 'True) (C1 ('MetaCons "ScriptHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash ADDRHASH EraIndependentScript)))) | |||||
type HASH = Blake2b_256 Source #
Hashing algorithm used for hashing everything, except addresses, for which ADDRHASH
is used.
class SafeToHash x ⇒ HashAnnotated x i | x → i where Source #
Types that are SafeToHash AND have the type uniquely determines the index type
tag of SafeHash index
The SafeToHash and the HashAnnotated classes are designed so that their instances
can be easily derived (because their methods have default methods when the type is a
newtype around a type that is SafeToHash). For example,
Minimal complete definition
Nothing
Methods
hashAnnotated ∷ x → SafeHash i Source #
Create a (, given SafeHash i)( instance.HashAnnotated x i)
Instances
| HashAnnotated AnchorData AnchorData Source # | |
Defined in Cardano.Ledger.BaseTypes Methods | |
| HashAnnotated (BinaryData era) EraIndependentData Source # | |
Defined in Cardano.Ledger.Plutus.Data Methods hashAnnotated ∷ BinaryData era → SafeHash EraIndependentData Source # | |
| HashAnnotated (Data era) EraIndependentData Source # | |
Defined in Cardano.Ledger.Plutus.Data Methods hashAnnotated ∷ Data era → SafeHash EraIndependentData Source # | |
A SafeHash is a hash of something that is safe to hash. Such types store their own
serialisation bytes. The prime example is (, but other examples are
things that consist of only ByteStrings (i.e. they are their own serialization) or for
some other reason store their original bytes.MemoBytes t)
We do NOT export the constructor SafeHash, but instead export other functions such as
hashAnnotated and extractHash which have constraints that limit their application
to types which preserve their original serialization bytes.
Instances
| FromJSON (SafeHash i) Source # | |
| ToJSON (SafeHash i) Source # | |
| Typeable i ⇒ FromCBOR (SafeHash i) Source # | |
| Typeable i ⇒ ToCBOR (SafeHash i) Source # | |
| Typeable i ⇒ DecCBOR (SafeHash i) Source # | |
| EncCBOR (SafeHash i) Source # | |
| SafeToHash (SafeHash i) Source # | |
Defined in Cardano.Ledger.Hashes Methods originalBytes ∷ SafeHash i → ByteString Source # originalBytesSize ∷ SafeHash i → Int Source # makeHashWithExplicitProxys ∷ Proxy i0 → SafeHash i → SafeHash i0 Source # | |
| Default (SafeHash i) Source # | |
Defined in Cardano.Ledger.Hashes | |
| NFData (SafeHash i) Source # | |
Defined in Cardano.Ledger.Hashes | |
| Show (SafeHash i) Source # | |
| Eq (SafeHash i) Source # | |
| Ord (SafeHash i) Source # | |
Defined in Cardano.Ledger.Hashes | |
| MemPack (SafeHash i) Source # | |
| NoThunks (SafeHash i) Source # | |
class SafeToHash t where Source #
Only Types that preserve their serialisation bytes are members of the
class SafeToHash. There are only a limited number of primitive direct
instances of SafeToHash, all but two of them are present in this file. Instead
of making explicit instances, we almost always use a newtype (around a type S)
where their is already an instance (SafeToHash S). In that case the newtype
has its SafeToHash instance derived using newtype deriving. The prime example of s is MemoBytes.
The only exceptions are the legacy Shelley types: Metadata and ShelleyTx, that
preserve their serialization bytes
using a different mechanism than the use of MemoBytes. SafeToHash is a superclass
requirement of the classes HashAnnotated which
provide more convenient ways to construct SafeHashes than using makeHashWithExplicitProxys.
Minimal complete definition
Methods
originalBytes ∷ t → ByteString Source #
Extract the original bytes from t
originalBytesSize ∷ t → Int Source #
makeHashWithExplicitProxys ∷ Proxy i → t → SafeHash i Source #
Instances
| SafeToHash ByteString Source # | |
Defined in Cardano.Ledger.Hashes Methods originalBytes ∷ ByteString → ByteString Source # originalBytesSize ∷ ByteString → Int Source # makeHashWithExplicitProxys ∷ Proxy i → ByteString → SafeHash i Source # | |
| SafeToHash ShortByteString Source # | |
Defined in Cardano.Ledger.Hashes Methods originalBytes ∷ ShortByteString → ByteString Source # originalBytesSize ∷ ShortByteString → Int Source # makeHashWithExplicitProxys ∷ Proxy i → ShortByteString → SafeHash i Source # | |
| SafeToHash AnchorData Source # | |
Defined in Cardano.Ledger.BaseTypes Methods originalBytes ∷ AnchorData → ByteString Source # originalBytesSize ∷ AnchorData → Int Source # makeHashWithExplicitProxys ∷ Proxy i → AnchorData → SafeHash i Source # | |
| SafeToHash PlutusBinary Source # | |
Defined in Cardano.Ledger.Plutus.Language Methods originalBytes ∷ PlutusBinary → ByteString Source # originalBytesSize ∷ PlutusBinary → Int Source # makeHashWithExplicitProxys ∷ Proxy i → PlutusBinary → SafeHash i Source # | |
| SafeToHash (SafeHash i) Source # | |
Defined in Cardano.Ledger.Hashes Methods originalBytes ∷ SafeHash i → ByteString Source # originalBytesSize ∷ SafeHash i → Int Source # makeHashWithExplicitProxys ∷ Proxy i0 → SafeHash i → SafeHash i0 Source # | |
| SafeToHash (MemoBytes t) Source # | |
Defined in Cardano.Ledger.MemoBytes.Internal Methods originalBytes ∷ MemoBytes t → ByteString Source # originalBytesSize ∷ MemoBytes t → Int Source # makeHashWithExplicitProxys ∷ Proxy i → MemoBytes t → SafeHash i Source # | |
| SafeToHash (BinaryData era) Source # | |
Defined in Cardano.Ledger.Plutus.Data Methods originalBytes ∷ BinaryData era → ByteString Source # originalBytesSize ∷ BinaryData era → Int Source # makeHashWithExplicitProxys ∷ Proxy i → BinaryData era → SafeHash i Source # | |
| SafeToHash (Data era) Source # | |
Defined in Cardano.Ledger.Plutus.Data Methods originalBytes ∷ Data era → ByteString Source # originalBytesSize ∷ Data era → Int Source # makeHashWithExplicitProxys ∷ Proxy i → Data era → SafeHash i Source # | |
| SafeToHash (Plutus l) Source # | |
Defined in Cardano.Ledger.Plutus.Language Methods originalBytes ∷ Plutus l → ByteString Source # originalBytesSize ∷ Plutus l → Int Source # makeHashWithExplicitProxys ∷ Proxy i → Plutus l → SafeHash i Source # | |
| HashAlgorithm h ⇒ SafeToHash (Hash h i) Source # | Hash of a hash. Hash is always safe to hash. Do you even hash? |
Defined in Cardano.Ledger.Hashes Methods originalBytes ∷ Hash h i → ByteString Source # originalBytesSize ∷ Hash h i → Int Source # makeHashWithExplicitProxys ∷ Proxy i0 → Hash h i → SafeHash i0 Source # | |
type ADDRHASH = Blake2b_224 Source #
Hashing algorithm used for hashing cryptographic keys and scripts. As the type synonym name alludes, this is the hashing algorithm used for addresses.
data EraIndependentTxBody Source #
data EraIndependentScript Source #
data EraIndependentData Source #
Instances
| HashAnnotated (BinaryData era) EraIndependentData Source # | |
Defined in Cardano.Ledger.Plutus.Data Methods hashAnnotated ∷ BinaryData era → SafeHash EraIndependentData Source # | |
| HashAnnotated (Data era) EraIndependentData Source # | |
Defined in Cardano.Ledger.Plutus.Data Methods hashAnnotated ∷ Data era → SafeHash EraIndependentData Source # | |
hashTxBodySignature ∷ SignedDSIGN DSIGN (Hash HASH EraIndependentTxBody) → Hash HASH (SignedDSIGN DSIGN (Hash HASH EraIndependentTxBody)) Source #
Hash a given signature
type DataHash = SafeHash EraIndependentData Source #
newtype TxAuxDataHash Source #
Constructors
| TxAuxDataHash | |
Instances
| ToJSON TxAuxDataHash Source # | |||||
Defined in Cardano.Ledger.Hashes Methods toJSON ∷ TxAuxDataHash → Value Source # toEncoding ∷ TxAuxDataHash → Encoding Source # toJSONList ∷ [TxAuxDataHash] → Value Source # | |||||
| DecCBOR TxAuxDataHash Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| EncCBOR TxAuxDataHash Source # | |||||
Defined in Cardano.Ledger.Hashes Methods | |||||
| NFData TxAuxDataHash Source # | |||||
Defined in Cardano.Ledger.Hashes Methods rnf ∷ TxAuxDataHash → () # | |||||
| Generic TxAuxDataHash Source # | |||||
Defined in Cardano.Ledger.Hashes Associated Types
| |||||
| Show TxAuxDataHash Source # | |||||
Defined in Cardano.Ledger.Hashes Methods showsPrec ∷ Int → TxAuxDataHash → ShowS # show ∷ TxAuxDataHash → String # showList ∷ [TxAuxDataHash] → ShowS # | |||||
| Eq TxAuxDataHash Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| Ord TxAuxDataHash Source # | |||||
Defined in Cardano.Ledger.Hashes Methods compare ∷ TxAuxDataHash → TxAuxDataHash → Ordering # (<) ∷ TxAuxDataHash → TxAuxDataHash → Bool # (<=) ∷ TxAuxDataHash → TxAuxDataHash → Bool # (>) ∷ TxAuxDataHash → TxAuxDataHash → Bool # (>=) ∷ TxAuxDataHash → TxAuxDataHash → Bool # | |||||
| NoThunks TxAuxDataHash Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| type Rep TxAuxDataHash Source # | |||||
Defined in Cardano.Ledger.Hashes type Rep TxAuxDataHash = D1 ('MetaData "TxAuxDataHash" "Cardano.Ledger.Hashes" "cardano-ledger-core-1.19.0.0-inplace" 'True) (C1 ('MetaCons "TxAuxDataHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTxAuxDataHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SafeHash EraIndependentTxAuxData)))) | |||||
data KeyRoleVRF Source #
Constructors
| StakePoolVRF | |
| GenDelegVRF | |
| BlockIssuerVRF |
newtype VRFVerKeyHash (r ∷ KeyRoleVRF) Source #
Discriminated hash of VRF Verification Key
Constructors
| VRFVerKeyHash | |
Fields | |
Instances
| FromJSON (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes Methods parseJSON ∷ Value → Parser (VRFVerKeyHash r) Source # parseJSONList ∷ Value → Parser [VRFVerKeyHash r] Source # omittedField ∷ Maybe (VRFVerKeyHash r) Source # | |||||
| FromJSONKey (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes Methods fromJSONKey ∷ FromJSONKeyFunction (VRFVerKeyHash r) Source # fromJSONKeyList ∷ FromJSONKeyFunction [VRFVerKeyHash r] Source # | |||||
| ToJSON (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes Methods toJSON ∷ VRFVerKeyHash r → Value Source # toEncoding ∷ VRFVerKeyHash r → Encoding Source # toJSONList ∷ [VRFVerKeyHash r] → Value Source # toEncodingList ∷ [VRFVerKeyHash r] → Encoding Source # omitField ∷ VRFVerKeyHash r → Bool Source # | |||||
| ToJSONKey (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes Methods toJSONKey ∷ ToJSONKeyFunction (VRFVerKeyHash r) Source # toJSONKeyList ∷ ToJSONKeyFunction [VRFVerKeyHash r] Source # | |||||
| Typeable r ⇒ FromCBOR (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| Typeable r ⇒ ToCBOR (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes Methods toCBOR ∷ VRFVerKeyHash r → Encoding Source # encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (VRFVerKeyHash r) → Size Source # encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [VRFVerKeyHash r] → Size Source # | |||||
| Typeable r ⇒ DecCBOR (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| EncCBOR (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes Methods encCBOR ∷ VRFVerKeyHash r → Encoding Source # | |||||
| Default (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes Methods def ∷ VRFVerKeyHash r Source # | |||||
| NFData (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes Methods rnf ∷ VRFVerKeyHash r → () # | |||||
| Generic (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes Associated Types
Methods from ∷ VRFVerKeyHash r → Rep (VRFVerKeyHash r) x # to ∷ Rep (VRFVerKeyHash r) x → VRFVerKeyHash r # | |||||
| Show (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes Methods showsPrec ∷ Int → VRFVerKeyHash r → ShowS # show ∷ VRFVerKeyHash r → String # showList ∷ [VRFVerKeyHash r] → ShowS # | |||||
| Eq (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes Methods (==) ∷ VRFVerKeyHash r → VRFVerKeyHash r → Bool # (/=) ∷ VRFVerKeyHash r → VRFVerKeyHash r → Bool # | |||||
| Ord (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes Methods compare ∷ VRFVerKeyHash r → VRFVerKeyHash r → Ordering # (<) ∷ VRFVerKeyHash r → VRFVerKeyHash r → Bool # (<=) ∷ VRFVerKeyHash r → VRFVerKeyHash r → Bool # (>) ∷ VRFVerKeyHash r → VRFVerKeyHash r → Bool # (>=) ∷ VRFVerKeyHash r → VRFVerKeyHash r → Bool # max ∷ VRFVerKeyHash r → VRFVerKeyHash r → VRFVerKeyHash r # min ∷ VRFVerKeyHash r → VRFVerKeyHash r → VRFVerKeyHash r # | |||||
| NoThunks (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| type Rep (VRFVerKeyHash r) Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
toVRFVerKeyHash ∷ ∀ v (r ∷ KeyRoleVRF). Hash HASH (VerKeyVRF v) → VRFVerKeyHash r Source #
fromVRFVerKeyHash ∷ ∀ (r ∷ KeyRoleVRF) v. VRFVerKeyHash r → Hash HASH (VerKeyVRF v) Source #
newtype HashHeader Source #
Constructors
| HashHeader | |
Instances
| DecCBOR HashHeader Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| EncCBOR HashHeader Source # | |||||
Defined in Cardano.Ledger.Hashes Methods encCBOR ∷ HashHeader → Encoding Source # | |||||
| NFData HashHeader Source # | |||||
Defined in Cardano.Ledger.Hashes Methods rnf ∷ HashHeader → () # | |||||
| Generic HashHeader Source # | |||||
Defined in Cardano.Ledger.Hashes Associated Types
| |||||
| Show HashHeader Source # | |||||
Defined in Cardano.Ledger.Hashes Methods showsPrec ∷ Int → HashHeader → ShowS # show ∷ HashHeader → String # showList ∷ [HashHeader] → ShowS # | |||||
| Eq HashHeader Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| Ord HashHeader Source # | |||||
Defined in Cardano.Ledger.Hashes Methods compare ∷ HashHeader → HashHeader → Ordering # (<) ∷ HashHeader → HashHeader → Bool # (<=) ∷ HashHeader → HashHeader → Bool # (>) ∷ HashHeader → HashHeader → Bool # (>=) ∷ HashHeader → HashHeader → Bool # max ∷ HashHeader → HashHeader → HashHeader # min ∷ HashHeader → HashHeader → HashHeader # | |||||
| NoThunks HashHeader Source # | |||||
Defined in Cardano.Ledger.Hashes | |||||
| type Rep HashHeader Source # | |||||
Defined in Cardano.Ledger.Hashes type Rep HashHeader = D1 ('MetaData "HashHeader" "Cardano.Ledger.Hashes" "cardano-ledger-core-1.19.0.0-inplace" 'True) (C1 ('MetaCons "HashHeader" 'PrefixI 'True) (S1 ('MetaSel ('Just "unHashHeader") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash HASH EraIndependentBlockHeader)))) | |||||
castSafeHash ∷ SafeHash i → SafeHash j Source #
To change the index parameter of SafeHash (which is a phantom type) use castSafeHash
data StakePoolVRF ∷ KeyRoleVRF Source #
data GenesisRole ∷ KeyRole Source #
data GenesisDelegate ∷ KeyRole Source #
data BlockIssuer ∷ KeyRole Source #
data HotCommitteeRole ∷ KeyRole Source #
data ColdCommitteeRole ∷ KeyRole Source #
data GenDelegVRF ∷ KeyRoleVRF Source #
data BlockIssuerVRF ∷ KeyRoleVRF Source #
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 #
Associated Types
type TxCert era = (r ∷ Type) | r → era Source #
type TxCertUpgradeError era Source #
type TxCertUpgradeError era = Void
Methods
upgradeTxCert ∷ 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) Source #
Return a witness key whenever a certificate requires one
getScriptWitnessTxCert ∷ TxCert era → Maybe ScriptHash Source #
Return a ScriptHash for certificate types that require a witness
mkRegPoolTxCert ∷ StakePoolParams → TxCert era Source #
getRegPoolTxCert ∷ TxCert era → Maybe StakePoolParams Source #
mkRetirePoolTxCert ∷ KeyHash 'StakePool → EpochNo → TxCert era Source #
getRetirePoolTxCert ∷ TxCert era → Maybe (KeyHash 'StakePool, EpochNo) Source #
lookupRegStakeTxCert ∷ TxCert era → Maybe (Credential 'Staking) Source #
Extract staking credential from any certificate that can register such credential
lookupUnRegStakeTxCert ∷ TxCert era → Maybe (Credential 'Staking) Source #
Extract staking credential from any certificate that can unregister such credential
getTotalDepositsTxCerts Source #
Arguments
| ∷ Foldable f | |
| ⇒ PParams era | |
| → (KeyHash 'StakePool → Bool) | Check whether stake pool is registered or not |
| → f (TxCert era) | |
| → Coin |
Compute the total deposits from a list of certificates.
getTotalRefundsTxCerts Source #
Arguments
| ∷ Foldable f | |
| ⇒ PParams era | |
| → (Credential 'Staking → Maybe Coin) | Lookup current deposit for Staking credential if one is registered |
| → (Credential 'DRepRole → 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 ⇒ StakePoolParams → TxCert era Source #
Constructors
| RegPool !StakePoolParams | A stake pool registration certificate. |
| RetirePool !(KeyHash 'StakePool) !EpochNo | A stake pool retirement certificate. |
Instances
| ToJSON PoolCert Source # | |||||
| EncCBOR PoolCert Source # | |||||
| NFData PoolCert Source # | |||||
Defined in Cardano.Ledger.Core.TxCert | |||||
| Generic PoolCert Source # | |||||
Defined in Cardano.Ledger.Core.TxCert Associated Types
| |||||
| Show PoolCert Source # | |||||
| Eq PoolCert Source # | |||||
| Ord PoolCert Source # | |||||
Defined in Cardano.Ledger.Core.TxCert | |||||
| NoThunks PoolCert Source # | |||||
| type Rep PoolCert Source # | |||||
Defined in Cardano.Ledger.Core.TxCert type Rep PoolCert = D1 ('MetaData "PoolCert" "Cardano.Ledger.Core.TxCert" "cardano-ledger-core-1.19.0.0-inplace" 'False) (C1 ('MetaCons "RegPool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 StakePoolParams)) :+: C1 ('MetaCons "RetirePool" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool)) :*: 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
type family TxCertUpgradeError era Source #
class (Era era, Eq (PParamsHKD Identity era), Ord (PParamsHKD Identity era), Show (PParamsHKD Identity era), NFData (PParamsHKD Identity era), NoThunks (PParamsHKD Identity era), Eq (PParamsHKD StrictMaybe era), Ord (PParamsHKD StrictMaybe era), Show (PParamsHKD StrictMaybe era), NFData (PParamsHKD StrictMaybe era), NoThunks (PParamsHKD StrictMaybe era)) ⇒ EraPParams era where Source #
Minimal complete definition
emptyPParamsIdentity, emptyPParamsStrictMaybe, upgradePParamsHKD, downgradePParamsHKD, hkdMinFeeAL, hkdMinFeeBL, hkdMaxBBSizeL, hkdMaxTxSizeL, hkdMaxBHSizeL, hkdKeyDepositL, hkdPoolDepositCompactL, hkdEMaxL, hkdNOptL, hkdA0L, hkdRhoL, hkdTauL, hkdDL, hkdExtraEntropyL, hkdProtocolVersionL, hkdMinUTxOValueL, hkdMinPoolCostL, eraPParams
Associated Types
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 Source #
type DowngradePParams (f ∷ Type → Type) era Source #
Methods
applyPPUpdates ∷ PParams era → PParamsUpdate era → PParams era Source #
Applies a protocol parameters update
default applyPPUpdates ∷ (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 #
emptyUpgradePParamsUpdate ∷ UpgradePParams StrictMaybe era Source #
default emptyUpgradePParamsUpdate ∷ UpgradePParams StrictMaybe era ~ () ⇒ UpgradePParams StrictMaybe era Source #
upgradePParamsHKD ∷ ∀ (f ∷ Type → Type). (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 ∷ ∀ (f ∷ Type → Type). (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 ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The linear factor for the minimum fee calculation
hkdMinFeeBL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The constant factor for the minimum fee calculation
hkdMaxBBSizeL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32) Source #
Maximal block body size
hkdMaxTxSizeL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32) Source #
Maximal transaction size
hkdMaxBHSizeL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16) Source #
Maximal block header size
hkdKeyDepositL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
The amount of a key registration deposit
hkdPoolDepositCompactL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f (CompactForm Coin)) Source #
The amount of a pool registration deposit
hkdEMaxL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f EpochInterval) Source #
epoch bound on pool retirement
hkdNOptL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16) Source #
Desired number of pools
hkdA0L ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f NonNegativeInterval) Source #
Pool influence
hkdRhoL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Monetary expansion
hkdTauL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Treasury expansion
hkdDL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #
Decentralization parameter
ppDG ∷ SimpleGetter (PParams era) UnitInterval Source #
Decentralization parameter getter
default ppDG ∷ AtMostEra "Alonzo" era ⇒ SimpleGetter (PParams era) UnitInterval Source #
hkdExtraEntropyL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsHKD f era) (HKD f Nonce) Source #
Extra entropy
hkdProtocolVersionL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Babbage" era) ⇒ Lens' (PParamsHKD f era) (HKD f ProtVer) Source #
Protocol version
ppProtocolVersionL ∷ Lens' (PParams era) ProtVer Source #
ppuProtocolVersionL ∷ Lens' (PParamsUpdate era) (StrictMaybe ProtVer) Source #
PParamsUpdate Protocol version
hkdMinUTxOValueL ∷ ∀ (f ∷ Type → Type). (HKDFunctor f, AtMostEra "Mary" era) ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
Minimum UTxO value
hkdMinPoolCostL ∷ ∀ (f ∷ Type → Type). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #
Minimum Stake Pool Cost
eraPParams ∷ [PParam era] Source #
Protocol parameters
Constructors
| PParams (PParamsHKD Identity era) |
Instances
| EraPParams era ⇒ FromJSON (PParams era) Source # | |||||
| EraPParams era ⇒ ToJSON (PParams era) Source # | |||||
| EraPParams era ⇒ FromCBOR (PParams era) Source # | |||||
| EraPParams era ⇒ ToCBOR (PParams era) Source # | |||||
| EraPParams era ⇒ DecCBOR (PParams era) Source # | |||||
| EraPParams era ⇒ EncCBOR (PParams era) Source # | |||||
| EraPParams era ⇒ ToKeyValuePairs (PParams era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Methods toKeyValuePairs ∷ KeyValue e kv ⇒ PParams era → [kv] Source # | |||||
| EraPParams era ⇒ Default (PParams era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams | |||||
| NFData (PParamsHKD Identity era) ⇒ NFData (PParams era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams | |||||
| Generic (PParams era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Associated Types
| |||||
| Show (PParamsHKD Identity era) ⇒ Show (PParams era) Source # | |||||
| Eq (PParamsHKD Identity era) ⇒ Eq (PParams era) Source # | |||||
| Ord (PParamsHKD Identity era) ⇒ Ord (PParams era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams | |||||
| NoThunks (PParamsHKD Identity era) ⇒ NoThunks (PParams era) Source # | |||||
| type Rep (PParams era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams type Rep (PParams era) = D1 ('MetaData "PParams" "Cardano.Ledger.Core.PParams" "cardano-ledger-core-1.19.0.0-inplace" 'True) (C1 ('MetaCons "PParams" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD Identity era)))) | |||||
data PParam era where Source #
Represents a single protocol parameter and the data required to serialize it.
data PParamUpdate era t Source #
Constructors
| PParamUpdate | |
Fields
| |
emptyPParams ∷ EraPParams era ⇒ PParams era Source #
newtype PParamsUpdate era Source #
The type of updates to Protocol parameters
Constructors
| PParamsUpdate (PParamsHKD StrictMaybe era) |
Instances
| EraPParams era ⇒ FromJSON (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Methods parseJSON ∷ Value → Parser (PParamsUpdate era) Source # parseJSONList ∷ Value → Parser [PParamsUpdate era] Source # omittedField ∷ Maybe (PParamsUpdate era) Source # | |||||
| EraPParams era ⇒ ToJSON (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Methods toJSON ∷ PParamsUpdate era → Value Source # toEncoding ∷ PParamsUpdate era → Encoding Source # toJSONList ∷ [PParamsUpdate era] → Value Source # toEncodingList ∷ [PParamsUpdate era] → Encoding Source # omitField ∷ PParamsUpdate era → Bool Source # | |||||
| EraPParams era ⇒ FromCBOR (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams | |||||
| EraPParams era ⇒ ToCBOR (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Methods toCBOR ∷ PParamsUpdate era → Encoding Source # encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (PParamsUpdate era) → Size Source # encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [PParamsUpdate era] → Size Source # | |||||
| EraPParams era ⇒ DecCBOR (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams | |||||
| EraPParams era ⇒ EncCBOR (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Methods encCBOR ∷ PParamsUpdate era → Encoding Source # | |||||
| EraPParams era ⇒ ToKeyValuePairs (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Methods toKeyValuePairs ∷ KeyValue e kv ⇒ PParamsUpdate era → [kv] Source # | |||||
| EraPParams era ⇒ Default (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Methods def ∷ PParamsUpdate era Source # | |||||
| NFData (PParamsHKD StrictMaybe era) ⇒ NFData (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Methods rnf ∷ PParamsUpdate era → () # | |||||
| Generic (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Associated Types
Methods from ∷ PParamsUpdate era → Rep (PParamsUpdate era) x # to ∷ Rep (PParamsUpdate era) x → PParamsUpdate era # | |||||
| Show (PParamsHKD StrictMaybe era) ⇒ Show (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Methods showsPrec ∷ Int → PParamsUpdate era → ShowS # show ∷ PParamsUpdate era → String # showList ∷ [PParamsUpdate era] → ShowS # | |||||
| Eq (PParamsHKD StrictMaybe era) ⇒ Eq (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Methods (==) ∷ PParamsUpdate era → PParamsUpdate era → Bool # (/=) ∷ PParamsUpdate era → PParamsUpdate era → Bool # | |||||
| Ord (PParamsHKD StrictMaybe era) ⇒ Ord (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams Methods compare ∷ PParamsUpdate era → PParamsUpdate era → Ordering # (<) ∷ PParamsUpdate era → PParamsUpdate era → Bool # (<=) ∷ PParamsUpdate era → PParamsUpdate era → Bool # (>) ∷ PParamsUpdate era → PParamsUpdate era → Bool # (>=) ∷ PParamsUpdate era → PParamsUpdate era → Bool # max ∷ PParamsUpdate era → PParamsUpdate era → PParamsUpdate era # min ∷ PParamsUpdate era → PParamsUpdate era → PParamsUpdate era # | |||||
| NoThunks (PParamsHKD StrictMaybe era) ⇒ NoThunks (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams | |||||
| type Rep (PParamsUpdate era) Source # | |||||
Defined in Cardano.Ledger.Core.PParams type Rep (PParamsUpdate era) = D1 ('MetaData "PParamsUpdate" "Cardano.Ledger.Core.PParams" "cardano-ledger-core-1.19.0.0-inplace" 'True) (C1 ('MetaCons "PParamsUpdate" 'PrefixI 'False) (S1 ('MetaSel ('Nothing ∷ Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD StrictMaybe era)))) | |||||
emptyPParamsUpdate ∷ EraPParams era ⇒ PParamsUpdate era Source #
genericApplyPPUpdates ∷ (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 #
ppMinFeeAL ∷ EraPParams era ⇒ Lens' (PParams era) Coin Source #
The linear factor for the minimum fee calculation
ppMinFeeBL ∷ EraPParams era ⇒ Lens' (PParams era) Coin Source #
The constant factor for the minimum fee calculation
ppMaxBBSizeL ∷ EraPParams era ⇒ Lens' (PParams era) Word32 Source #
Maximal block body size
ppMaxTxSizeL ∷ EraPParams era ⇒ Lens' (PParams era) Word32 Source #
Maximal transaction size
ppMaxBHSizeL ∷ EraPParams era ⇒ Lens' (PParams era) Word16 Source #
Maximal block header size
ppKeyDepositL ∷ EraPParams era ⇒ Lens' (PParams era) Coin Source #
The amount of a key registration deposit
ppPoolDepositL ∷ (EraPParams era, HasCallStack) ⇒ Lens' (PParams era) Coin Source #
The amount of a pool registration deposit
ppPoolDepositCompactL ∷ EraPParams era ⇒ Lens' (PParams era) (CompactForm Coin) Source #
The amount of a pool registration deposit in compacted form
ppEMaxL ∷ EraPParams era ⇒ Lens' (PParams era) EpochInterval Source #
epoch bound on pool retirement
ppA0L ∷ EraPParams era ⇒ Lens' (PParams era) NonNegativeInterval Source #
Pool influence
ppRhoL ∷ EraPParams era ⇒ Lens' (PParams era) UnitInterval Source #
Monetary expansion
ppTauL ∷ EraPParams era ⇒ Lens' (PParams era) UnitInterval Source #
Treasury expansion
ppDL ∷ (EraPParams era, AtMostEra "Alonzo" era) ⇒ Lens' (PParams era) UnitInterval Source #
Decentralization parameter
ppExtraEntropyL ∷ (EraPParams era, AtMostEra "Alonzo" era) ⇒ Lens' (PParams era) Nonce Source #
Extra entropy
ppMinUTxOValueL ∷ (EraPParams era, AtMostEra "Mary" era) ⇒ Lens' (PParams era) Coin Source #
Minimum UTxO value
ppMinPoolCostL ∷ EraPParams era ⇒ Lens' (PParams era) Coin Source #
Minimum Stake Pool Cost
ppuMinFeeAL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #
The linear factor for the minimum fee calculation
ppuMinFeeBL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #
The constant factor for the minimum fee calculation
ppuMaxBBSizeL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word32) Source #
Maximal block body size
ppuMaxTxSizeL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word32) Source #
Maximal transaction size
ppuMaxBHSizeL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word16) Source #
Maximal block header size
ppuKeyDepositL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #
The amount of a key registration deposit
ppuPoolDepositL ∷ (EraPParams era, HasCallStack) ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #
The amount of a pool registration deposit. The value must be small enough to fit into a Word64.
ppuPoolDepositCompactL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe (CompactForm Coin)) Source #
The amount of a pool registration deposit in compacted form
ppuEMaxL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe EpochInterval) Source #
epoch bound on pool retirement
ppuNOptL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word16) Source #
Desired number of pools
ppuA0L ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe NonNegativeInterval) Source #
Pool influence
ppuRhoL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval) Source #
Monetary expansion
ppuTauL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval) Source #
Treasury expansion
ppuDL ∷ (EraPParams era, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval) Source #
Decentralization parameter
ppuExtraEntropyL ∷ (EraPParams era, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsUpdate era) (StrictMaybe Nonce) Source #
Extra entropy
ppuMinUTxOValueL ∷ (EraPParams era, AtMostEra "Mary" era) ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #
Minimum UTxO value
ppuMinPoolCostL ∷ EraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #
Minimum Stake Pool Cost
ppLensHKD ∷ ∀ era f. Functor f ⇒ (PParamsHKD Identity era → f (PParamsHKD Identity era)) → PParams era → f (PParams era) Source #
ppuLensHKD ∷ ∀ era f. Functor f ⇒ (PParamsHKD StrictMaybe era → f (PParamsHKD StrictMaybe era)) → PParamsUpdate era → f (PParamsUpdate 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 #
type family PParamsHKD (f ∷ Type → Type) era = (r ∷ Type) | r → era Source #
Protocol parameters where the fields are represented with a HKD
type family UpgradePParams (f ∷ Type → Type) era Source #
type family DowngradePParams (f ∷ Type → Type) era Source #
type family PreviousEra era = (r ∷ Type) | r → era Source #
Map an era to its predecessor.
For example:
type instance PreviousEra AllegraEra = ShelleyEra
Instances
| type PreviousEra AllegraEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra AlonzoEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra BabbageEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra ByronEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra ConwayEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra DijkstraEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra MaryEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra ShelleyEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
type family PreviousEra era = (r ∷ Type) | r → era Source #
Map an era to its predecessor.
For example:
type instance PreviousEra AllegraEra = ShelleyEra
Instances
| type PreviousEra AllegraEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra AlonzoEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra BabbageEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra ByronEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra ConwayEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra DijkstraEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra MaryEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
| type PreviousEra ShelleyEra | |
Defined in Cardano.Ledger.Internal.Definition.Era | |
type family TranslationContext era 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).
class (Era era, Era (PreviousEra era)) ⇒ TranslateEra era (f ∷ Type → Type) where 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 AllegraEra 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 TranslateEra AllegraEra Bar where
translateEra ctxt = Bar <$> translateEra ctxt
-- With the following instance being in scope:
instance TranslatEra AllegraEra TxBodyNote: 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.
Minimal complete definition
Nothing
Associated Types
type TranslationError era (f ∷ Type → 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.
type TranslationError era (f ∷ Type → Type) = Void
Methods
translateEra ∷ 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.
default translateEra ∷ (Coercible (f (PreviousEra era)) (f era), TranslationContext era ~ NoGenesis era) ⇒ TranslationContext era → f (PreviousEra era) → Except (TranslationError era f) (f era) Source #
type family TranslationError era (f ∷ Type → 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.
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 #
Arguments
| ∷ (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.