cardano-ledger-core-1.19.0.0: Core components of Cardano ledgers from the Shelley release on.
Safe HaskellNone
LanguageHaskell2010

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

Transaction types

data TxLevel Source #

Constructors

TopTx 
SubTx 

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 ∷ TxLevelTypeType) 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.

Associated Types

data Tx (l ∷ TxLevel) era Source #

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). HasCallStackSimpleGetter (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.

getMinFeeTx Source #

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

txIdTx ∷ ∀ era (l ∷ TxLevel). EraTx era ⇒ Tx l era → TxId Source #

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

Associated Types

type TxOut era = (r ∷ Type) | r → era Source #

The output of a UTxO for a particular era

Methods

mkBasicTxOutAddrValue era → TxOut era Source #

upgradeTxOutTxOut (PreviousEra era) → TxOut era Source #

Every era, except Shelley, must be able to upgrade a TxOut from a previous era.

valueTxOutLLens' (TxOut era) (Value era) Source #

compactValueTxOutLLens' (TxOut era) (CompactForm (Value era)) Source #

valueEitherTxOutLLens' (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.

addrTxOutLLens' (TxOut era) Addr Source #

compactAddrTxOutLLens' (TxOut era) CompactAddr Source #

addrEitherTxOutLLens' (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)

getMinCoinSizedTxOutPParams 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.

getMinCoinTxOutPParams 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.

isAdaOnlyTxOutFEraTxOut 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 #

Associated Types

data TxBody (l ∷ TxLevel) era Source #

The body of a transaction.

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 #

feeTxBodyLLens' (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.

allInputsTxBodyFSimpleGetter (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 'StakePoolBool)

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 'StakingMaybe Coin)

Lookup current deposit for Staking credential if one is registered

→ (Credential 'DRepRoleMaybe 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

getGenesisKeyHashCountTxBodyTxBody '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.

txIdTxBody ∷ ∀ era (l ∷ TxLevel). EraTxBody era ⇒ TxBody l era → TxId Source #

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

Associated Types

type TxAuxData era = (r ∷ Type) | r → era Source #

hashTxAuxDataEraTxAuxData 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

addrTxWitsL, bootAddrTxWitsL, scriptTxWitsL

Associated Types

type TxWits era = (r ∷ Type) | r → 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

upgradeScriptScript (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

scriptPrefixTagScript era → ByteString Source #

getNativeScriptScript era → Maybe (NativeScript era) Source #

fromNativeScriptNativeScript era → Script era Source #

hashScriptEraScript era ⇒ Script era → ScriptHash Source #

Compute ScriptHash of a Script for a particular era.

hashScriptTxWitsLEraTxWits 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.

keyHashWitnessesTxWitsEraTxWits era ⇒ TxWits era → Set (KeyHash 'Witness) Source #

Extract all of the KeyHash witnesses provided in the TxWits

type family Value era Source #

A value is something which quantifies a transaction output.

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 #

Associated Types

type PParamsHKD (f ∷ TypeType) era = (r ∷ Type) | r → era Source #

Protocol parameters where the fields are represented with a HKD

type UpgradePParams (f ∷ TypeType) era Source #

type DowngradePParams (f ∷ TypeType) era Source #

Methods

applyPPUpdatesPParams 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 #

emptyPParamsIdentityPParamsHKD Identity era Source #

emptyPParamsStrictMaybePParamsHKD StrictMaybe era Source #

emptyUpgradePParamsUpdateUpgradePParams StrictMaybe era Source #

upgradePParamsHKD ∷ ∀ (f ∷ TypeType). (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 ∷ TypeType). (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 ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #

The linear factor for the minimum fee calculation

hkdMinFeeBL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #

The constant factor for the minimum fee calculation

hkdMaxBBSizeL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32) Source #

Maximal block body size

hkdMaxTxSizeL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32) Source #

Maximal transaction size

hkdMaxBHSizeL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16) Source #

Maximal block header size

hkdKeyDepositL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #

The amount of a key registration deposit

hkdPoolDepositCompactL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f (CompactForm Coin)) Source #

The amount of a pool registration deposit

hkdEMaxL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f EpochInterval) Source #

epoch bound on pool retirement

hkdNOptL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16) Source #

Desired number of pools

hkdA0L ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f NonNegativeInterval) Source #

Pool influence

hkdRhoL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #

Monetary expansion

hkdTauL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #

Treasury expansion

hkdDL ∷ ∀ (f ∷ TypeType). (HKDFunctor f, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #

Decentralization parameter

ppDGSimpleGetter (PParams era) UnitInterval Source #

Decentralization parameter getter

default ppDGAtMostEra "Alonzo" era ⇒ SimpleGetter (PParams era) UnitInterval Source #

hkdExtraEntropyL ∷ ∀ (f ∷ TypeType). (HKDFunctor f, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsHKD f era) (HKD f Nonce) Source #

Extra entropy

hkdProtocolVersionL ∷ ∀ (f ∷ TypeType). (HKDFunctor f, AtMostEra "Babbage" era) ⇒ Lens' (PParamsHKD f era) (HKD f ProtVer) Source #

Protocol version

ppProtocolVersionLLens' (PParams era) ProtVer Source #

default ppProtocolVersionLAtMostEra "Babbage" era ⇒ Lens' (PParams era) ProtVer Source #

ppuProtocolVersionLLens' (PParamsUpdate era) (StrictMaybe ProtVer) Source #

PParamsUpdate Protocol version

hkdMinUTxOValueL ∷ ∀ (f ∷ TypeType). (HKDFunctor f, AtMostEra "Mary" era) ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #

Minimum UTxO value

hkdMinPoolCostL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #

Minimum Stake Pool Cost

eraPParams ∷ [PParam era] Source #

mkCoinTxOutEraTxOut era ⇒ AddrCoinTxOut 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

data ByronEra Source #

This is the era that preceded Shelley era. It cannot have any other class instances, except for Era type class.

Instances

Instances details
Era ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Associated Types

type EraName ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName ByronEra = "Byron"
type PreviousEra ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type PreviousEra ByronEra = VoidEra
type ProtVerLow ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type ProtVerHigh ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Methods

eraNameString Source #

type EraName ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName ByronEra = "Byron"
type PreviousEra ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type PreviousEra ByronEra = VoidEra
type ProtVerHigh ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type ProtVerLow ByronEra 
Instance details

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

eraNameString Source #

Textual name of the current era.

Designed to be used with TypeApplications:

>>> eraName @ByronEra
"Byron"

default eraNameKnownSymbol (EraName era) ⇒ String Source #

Instances

Instances details
Era AllegraEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Methods

eraNameString Source #

Era AlonzoEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Associated Types

type EraName AlonzoEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName AlonzoEra = "Alonzo"
type PreviousEra AlonzoEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type ProtVerLow AlonzoEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type ProtVerHigh AlonzoEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Methods

eraNameString Source #

Era BabbageEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Methods

eraNameString Source #

Era ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Associated Types

type EraName ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName ByronEra = "Byron"
type PreviousEra ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type PreviousEra ByronEra = VoidEra
type ProtVerLow ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type ProtVerHigh ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Methods

eraNameString Source #

Era ConwayEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Associated Types

type EraName ConwayEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName ConwayEra = "Conway"
type PreviousEra ConwayEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type ProtVerLow ConwayEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type ProtVerHigh ConwayEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Methods

eraNameString Source #

Era DijkstraEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Methods

eraNameString Source #

Era MaryEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Methods

eraNameString Source #

Era ShelleyEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

Methods

eraNameString Source #

type family EraName era ∷ Symbol Source #

Instances

Instances details
type EraName AllegraEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName AllegraEra = "Allegra"
type EraName AlonzoEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName AlonzoEra = "Alonzo"
type EraName BabbageEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName BabbageEra = "Babbage"
type EraName ByronEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName ByronEra = "Byron"
type EraName ConwayEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName ConwayEra = "Conway"
type EraName DijkstraEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName DijkstraEra = "Dijkstra"
type EraName MaryEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName MaryEra = "Mary"
type EraName ShelleyEra 
Instance details

Defined in Cardano.Ledger.Internal.Definition.Era

type EraName ShelleyEra = "Shelley"

type family PreviousEra era = (r ∷ Type) | r → era Source #

Map an era to its predecessor.

For example:

type instance PreviousEra AllegraEra = ShelleyEra

type family ProtVerLow era ∷ Nat Source #

Lowest major protocol version for this era

type family ProtVerHigh era ∷ Nat Source #

Highest major protocol version for this era. By default se to ProtVerLow

eraProtVerLowEra era ⇒ Version Source #

Get the value level Version of the lowest major protocol version for the supplied era.

type family EraRule (rule ∷ Symbol) era = (r ∷ Type) | r → rule Source #

Era STS map

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

Instances details
type EraRuleFailure "EPOCH" era Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraRuleFailure "EPOCH" era = VoidEraRule "EPOCH" era
type EraRuleFailure "MIR" era Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraRuleFailure "MIR" era = VoidEraRule "MIR" era
type EraRuleFailure "NEWEPOCH" era Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraRuleFailure "NEWEPOCH" era = VoidEraRule "NEWEPOCH" era
type EraRuleFailure "NEWPP" era Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraRuleFailure "NEWPP" era = VoidEraRule "NEWPP" era
type EraRuleFailure "POOLREAP" era Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraRuleFailure "POOLREAP" era = VoidEraRule "POOLREAP" era
type EraRuleFailure "RUPD" era Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraRuleFailure "RUPD" era = VoidEraRule "RUPD" era
type EraRuleFailure "SNAP" era Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraRuleFailure "SNAP" era = VoidEraRule "SNAP" era
type EraRuleFailure "TICK" era Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraRuleFailure "TICK" era = VoidEraRule "TICK" era
type EraRuleFailure "TICKF" era Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraRuleFailure "TICKF" era = VoidEraRule "TICKF" era
type EraRuleFailure "UPEC" era Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraRuleFailure "UPEC" era = VoidEraRule "UPEC" 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

Instances details
(KnownSymbol rule, Era era) ⇒ FromCBOR (VoidEraRule rule era) Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

fromCBORDecoder s (VoidEraRule rule era) Source #

labelProxy (VoidEraRule rule era) → Text Source #

(KnownSymbol rule, Era era) ⇒ ToCBOR (VoidEraRule rule era) Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

toCBORVoidEraRule 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 # 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

decCBORDecoder s (VoidEraRule rule era) Source #

dropCBORProxy (VoidEraRule rule era) → Decoder s () Source #

labelProxy (VoidEraRule rule era) → Text Source #

(KnownSymbol rule, Era era) ⇒ EncCBOR (VoidEraRule rule era) Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

encCBORVoidEraRule rule era → Encoding Source #

NFData (VoidEraRule rule era) Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

rnfVoidEraRule rule era → () #

Show (VoidEraRule rule era) Source # 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

showsPrecIntVoidEraRule rule era → ShowS #

showVoidEraRule rule era → String #

showList ∷ [VoidEraRule rule era] → ShowS #

Eq (VoidEraRule rule era) Source # 
Instance details

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 # 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

compareVoidEraRule 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 #

maxVoidEraRule rule era → VoidEraRule rule era → VoidEraRule rule era #

minVoidEraRule 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 ∷ TypeType) 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 ∷ TypeType) 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

eraProtVerHighEra era ⇒ Version Source #

Get the value level Version of the highest major protocol version for the supplied era.

eraProtVersionsEra era ⇒ [Version] Source #

List with all major versions that are used in the particular era.

toEraCBOR ∷ (Era era, EncCBOR t) ⇒ t → Encoding Source #

Convert a type that implements EncCBOR to plain Encoding using the lowest protocol version for the supplied 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 ⇒ ByteStringDecoder 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.

Associated Types

type BlockBody era = (r ∷ Type) | r → era Source #

Methods

mkBasicBlockBodyBlockBody era Source #

txSeqBlockBodyLLens' (BlockBody era) (StrictSeq (Tx 'TopTx era)) Source #

hashBlockBodyBlockBody 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.

numSegComponentsWord64 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

Instances details
ToJSON RewardType Source # 
Instance details

Defined in Cardano.Ledger.Rewards

DecCBOR RewardType Source # 
Instance details

Defined in Cardano.Ledger.Rewards

EncCBOR RewardType Source # 
Instance details

Defined in Cardano.Ledger.Rewards

NFData RewardType Source # 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

rnfRewardType → () #

Bounded RewardType Source # 
Instance details

Defined in Cardano.Ledger.Rewards

Enum RewardType Source # 
Instance details

Defined in Cardano.Ledger.Rewards

Generic RewardType Source # 
Instance details

Defined in Cardano.Ledger.Rewards

Associated Types

type Rep RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

type Rep RewardType = D1 ('MetaData "RewardType" "Cardano.Ledger.Rewards" "cardano-ledger-core-1.19.0.0-inplace" 'False) (C1 ('MetaCons "MemberReward" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "LeaderReward" 'PrefixI 'False) (U1TypeType))
Show RewardType Source # 
Instance details

Defined in Cardano.Ledger.Rewards

Eq RewardType Source # 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

(==)RewardTypeRewardTypeBool #

(/=)RewardTypeRewardTypeBool #

Ord RewardType Source # 
Instance details

Defined in Cardano.Ledger.Rewards

NoThunks RewardType Source # 
Instance details

Defined in Cardano.Ledger.Rewards

type Rep RewardType Source # 
Instance details

Defined in Cardano.Ledger.Rewards

type Rep RewardType = D1 ('MetaData "RewardType" "Cardano.Ledger.Rewards" "cardano-ledger-core-1.19.0.0-inplace" 'False) (C1 ('MetaCons "MemberReward" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "LeaderReward" 'PrefixI 'False) (U1TypeType))

data Reward 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 

Instances

Instances details
ToJSON Reward Source # 
Instance details

Defined in Cardano.Ledger.Rewards

DecCBOR Reward Source # 
Instance details

Defined in Cardano.Ledger.Rewards

EncCBOR Reward Source # 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

encCBORRewardEncoding Source #

ToKeyValuePairs Reward Source # 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

toKeyValuePairsKeyValue e kv ⇒ Reward → [kv] Source #

NFData Reward Source # 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

rnfReward → () #

Generic Reward Source # 
Instance details

Defined in Cardano.Ledger.Rewards

Associated Types

type Rep Reward 
Instance details

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))))

Methods

fromRewardRep Reward x #

toRep Reward x → Reward #

Show Reward Source # 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

showsPrecIntRewardShowS #

showRewardString #

showList ∷ [Reward] → ShowS #

Eq Reward Source # 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

(==)RewardRewardBool #

(/=)RewardRewardBool #

Ord Reward Source #

Note that this Ord instance is chosen to align precisely with the Allegra reward aggregation, as given by the function aggregateRewards so that findMax returns the expected value.

Instance details

Defined in Cardano.Ledger.Rewards

Methods

compareRewardRewardOrdering #

(<)RewardRewardBool #

(<=)RewardRewardBool #

(>)RewardRewardBool #

(>=)RewardRewardBool #

maxRewardRewardReward #

minRewardRewardReward #

NoThunks Reward Source # 
Instance details

Defined in Cardano.Ledger.Rewards

type Rep Reward Source # 
Instance details

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

data KeyRole Source #

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.

data Hash h a Source #

Instances

Instances details
HashAlgorithm h ⇒ IsString (Q (TExp (Hash h a)))

This instance is meant to be used with TemplateHaskell

>>> import Cardano.Crypto.Hash.Class (Hash)
>>> import Cardano.Crypto.Hash.Short (ShortHash)
>>> :set -XTemplateHaskell
>>> :set -XOverloadedStrings
>>>  let hash = $$("0xBADC0FFEE0DDF00D") :: Hash ShortHash ()
>>> print hash
"badc0ffee0ddf00d"
>>> let hash = $$("0123456789abcdef") :: Hash ShortHash ()
>>> print hash
"0123456789abcdef"
>>> let hash = $$("deadbeef") :: Hash ShortHash ()
<interactive>:5:15: error:
    • <Hash blake2b_prefix_8>: Expected in decoded form to be: 8 bytes, but got: 4
    • In the Template Haskell splice $$("deadbeef")
      In the expression: $$("deadbeef") :: Hash ShortHash ()
      In an equation for ‘hash’:
          hash = $$("deadbeef") :: Hash ShortHash ()
>>> let hash = $$("123") :: Hash ShortHash ()
<interactive>:6:15: error:
    • <Hash blake2b_prefix_8>: Malformed hex: invalid bytestring size
    • In the Template Haskell splice $$("123")
      In the expression: $$("123") :: Hash ShortHash ()
      In an equation for ‘hash’: hash = $$("123") :: Hash ShortHash ()
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

fromStringStringQ (TExp (Hash h a)) #

HashAlgorithm h ⇒ FromJSON (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

HashAlgorithm h ⇒ FromJSONKey (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

HashAlgorithm h ⇒ ToJSON (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

toJSONHash h a → Value Source #

toEncodingHash h a → Encoding Source #

toJSONList ∷ [Hash h a] → Value Source #

toEncodingList ∷ [Hash h a] → Encoding Source #

omitFieldHash h a → Bool Source #

HashAlgorithm h ⇒ ToJSONKey (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

(HashAlgorithm h, Typeable a) ⇒ FromCBOR (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

fromCBORDecoder s (Hash h a) Source #

labelProxy (Hash h a) → Text Source #

(HashAlgorithm h, Typeable a) ⇒ ToCBOR (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

toCBORHash h a → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (Hash h a) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [Hash h a] → Size Source #

SignableRepresentation (Hash a b) Source # 
Instance details

Defined in Cardano.Ledger.Orphans

(HashAlgorithm h, Typeable a) ⇒ DecCBOR (Hash h a) 
Instance details

Defined in Cardano.Ledger.Binary.Decoding.DecCBOR

Methods

decCBORDecoder s (Hash h a) Source #

dropCBORProxy (Hash h a) → Decoder s () Source #

labelProxy (Hash h a) → Text Source #

HashAlgorithm h ⇒ EncCBOR (Hash h a) 
Instance details

Defined in Cardano.Ledger.Binary.Encoding.EncCBOR

Methods

encCBORHash h a → Encoding Source #

HashAlgorithm h ⇒ SafeToHash (Hash h i) Source #

Hash of a hash. Hash is always safe to hash. Do you even hash?

Instance details

Defined in Cardano.Ledger.Hashes

HashAlgorithm h ⇒ Default (Hash h b) Source # 
Instance details

Defined in Cardano.Ledger.Orphans

Methods

defHash h b Source #

NFData (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

rnfHash h a → () #

HashAlgorithm h ⇒ IsString (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

fromStringStringHash h a #

Generic (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Associated Types

type Rep (Hash h a) 
Instance details

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 ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PackedBytes (SizeHash h)))))

Methods

fromHash h a → Rep (Hash h a) x #

toRep (Hash h a) x → Hash h a #

HashAlgorithm h ⇒ Read (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

readsPrecIntReadS (Hash h a) #

readListReadS [Hash h a] #

readPrecReadPrec (Hash h a) #

readListPrecReadPrec [Hash h a] #

Show (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

showsPrecIntHash h a → ShowS #

showHash h a → String #

showList ∷ [Hash h a] → ShowS #

Eq (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

(==)Hash h a → Hash h a → Bool #

(/=)Hash h a → Hash h a → Bool #

Ord (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

compareHash h a → Hash h a → Ordering #

(<)Hash h a → Hash h a → Bool #

(<=)Hash h a → Hash h a → Bool #

(>)Hash h a → Hash h a → Bool #

(>=)Hash h a → Hash h a → Bool #

maxHash h a → Hash h a → Hash h a #

minHash h a → Hash h a → Hash h a #

HeapWords (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

heapWordsHash h a → Int Source #

HashAlgorithm h ⇒ MemPack (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

typeNameString Source #

packedByteCountHash h a → Int Source #

packMHash h a → Pack s () Source #

unpackMBuffer b ⇒ Unpack s b (Hash h a) Source #

NoThunks (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

HashAlgorithm h ⇒ IsString (Code Q (Hash h a)) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

fromStringStringCode Q (Hash h a) #

type Rep (Hash h a) 
Instance details

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 ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PackedBytes (SizeHash h)))))

class (KnownNat (SizeHash h), Typeable h) ⇒ HashAlgorithm h Source #

Minimal complete definition

hashAlgorithmName, digest

Instances

Instances details
HashAlgorithm Blake2b_224 
Instance details

Defined in Cardano.Crypto.Hash.Blake2b

Associated Types

type SizeHash Blake2b_224 
Instance details

Defined in Cardano.Crypto.Hash.Blake2b

HashAlgorithm Blake2b_256 
Instance details

Defined in Cardano.Crypto.Hash.Blake2b

Associated Types

type SizeHash Blake2b_256 
Instance details

Defined in Cardano.Crypto.Hash.Blake2b

HashAlgorithm Keccak256 
Instance details

Defined in Cardano.Crypto.Hash.Keccak256

Associated Types

type SizeHash Keccak256 
Instance details

Defined in Cardano.Crypto.Hash.Keccak256

HashAlgorithm NeverHash 
Instance details

Defined in Cardano.Crypto.Hash.NeverUsed

Associated Types

type SizeHash NeverHash 
Instance details

Defined in Cardano.Crypto.Hash.NeverUsed

HashAlgorithm RIPEMD160 
Instance details

Defined in Cardano.Crypto.Hash.RIPEMD160

Associated Types

type SizeHash RIPEMD160 
Instance details

Defined in Cardano.Crypto.Hash.RIPEMD160

HashAlgorithm SHA256 
Instance details

Defined in Cardano.Crypto.Hash.SHA256

Associated Types

type SizeHash SHA256 
Instance details

Defined in Cardano.Crypto.Hash.SHA256

type SizeHash SHA256 = 32
HashAlgorithm SHA3_256 
Instance details

Defined in Cardano.Crypto.Hash.SHA3_256

Associated Types

type SizeHash SHA3_256 
Instance details

Defined in Cardano.Crypto.Hash.SHA3_256

type SizeHash SHA3_256 = 32
HashAlgorithm SHA3_512 
Instance details

Defined in Cardano.Crypto.Hash.SHA3_512

Associated Types

type SizeHash SHA3_512 
Instance details

Defined in Cardano.Crypto.Hash.SHA3_512

type SizeHash SHA3_512 = 64
HashAlgorithm SHA512 
Instance details

Defined in Cardano.Crypto.Hash.SHA512

Associated Types

type SizeHash SHA512 
Instance details

Defined in Cardano.Crypto.Hash.SHA512

type SizeHash SHA512 = 64
(KnownNat n, CmpNat n 33 ~ 'LT) ⇒ HashAlgorithm (Blake2bPrefix n) 
Instance details

Defined in Cardano.Crypto.Hash.Short

Associated Types

type SizeHash (Blake2bPrefix n) 
Instance details

Defined in Cardano.Crypto.Hash.Short

type SizeHash (Blake2bPrefix n) = n

newtype KeyHash (r ∷ KeyRole) Source #

Discriminated hash of public Key

Constructors

KeyHash 

Instances

Instances details
HasKeyRole KeyHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

coerceKeyRole ∷ ∀ (r ∷ KeyRole) (r' ∷ KeyRole). KeyHash r → KeyHash r' Source #

FromJSON (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

FromJSONKey (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSON (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSONKey (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable r ⇒ FromCBOR (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

fromCBORDecoder s (KeyHash r) Source #

labelProxy (KeyHash r) → Text Source #

Typeable r ⇒ ToCBOR (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

toCBORKeyHash r → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (KeyHash r) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [KeyHash r] → Size Source #

Typeable r ⇒ DecCBOR (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

decCBORDecoder s (KeyHash r) Source #

dropCBORProxy (KeyHash r) → Decoder s () Source #

labelProxy (KeyHash r) → Text Source #

EncCBOR (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

encCBORKeyHash r → Encoding Source #

Default (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

defKeyHash r Source #

NFData (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

rnfKeyHash r → () #

Generic (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Associated Types

type Rep (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

fromKeyHash r → Rep (KeyHash r) x #

toRep (KeyHash r) x → KeyHash r #

Show (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

showsPrecIntKeyHash r → ShowS #

showKeyHash r → String #

showList ∷ [KeyHash r] → ShowS #

Eq (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

(==)KeyHash r → KeyHash r → Bool #

(/=)KeyHash r → KeyHash r → Bool #

Ord (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

compareKeyHash r → KeyHash r → Ordering #

(<)KeyHash r → KeyHash r → Bool #

(<=)KeyHash r → KeyHash r → Bool #

(>)KeyHash r → KeyHash r → Bool #

(>=)KeyHash r → KeyHash r → Bool #

maxKeyHash r → KeyHash r → KeyHash r #

minKeyHash r → KeyHash r → KeyHash r #

MemPack (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

NoThunks (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

type Rep (KeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

hashKey ∷ ∀ (kd ∷ KeyRole). VKey kd → KeyHash kd Source #

Hash a given public key

newtype ScriptHash Source #

Instances

Instances details
FromJSON ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

FromJSONKey ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSON ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSONKey ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

FromCBOR ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

ToCBOR ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

toCBORScriptHashEncoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy ScriptHashSize Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [ScriptHash] → Size Source #

DecCBOR ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

EncCBOR ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

NFData ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

rnfScriptHash → () #

Generic ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Associated Types

type Rep ScriptHash 
Instance details

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 ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash ADDRHASH EraIndependentScript))))
Show ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Eq ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

(==)ScriptHashScriptHashBool #

(/=)ScriptHashScriptHashBool #

Ord ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

MemPack ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

NoThunks ScriptHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

type Rep ScriptHash Source # 
Instance details

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 ('NothingMaybe 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 (SafeHash i), given (HashAnnotated x i) instance.

data SafeHash i Source #

A SafeHash is a hash of something that is safe to hash. Such types store their own serialisation bytes. The prime example is (MemoBytes t), 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.

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

Instances details
FromJSON (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSON (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable i ⇒ FromCBOR (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable i ⇒ ToCBOR (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

toCBORSafeHash i → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (SafeHash i) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [SafeHash i] → Size Source #

Typeable i ⇒ DecCBOR (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

EncCBOR (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

encCBORSafeHash i → Encoding Source #

SafeToHash (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Default (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

defSafeHash i Source #

NFData (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

rnfSafeHash i → () #

Show (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

showsPrecIntSafeHash i → ShowS #

showSafeHash i → String #

showList ∷ [SafeHash i] → ShowS #

Eq (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

(==)SafeHash i → SafeHash i → Bool #

(/=)SafeHash i → SafeHash i → Bool #

Ord (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

compareSafeHash i → SafeHash i → Ordering #

(<)SafeHash i → SafeHash i → Bool #

(<=)SafeHash i → SafeHash i → Bool #

(>)SafeHash i → SafeHash i → Bool #

(>=)SafeHash i → SafeHash i → Bool #

maxSafeHash i → SafeHash i → SafeHash i #

minSafeHash i → SafeHash i → SafeHash i #

MemPack (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

NoThunks (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

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

originalBytes

Methods

originalBytes ∷ t → ByteString Source #

Extract the original bytes from t

originalBytesSize ∷ t → Int Source #

makeHashWithExplicitProxysProxy i → t → SafeHash i Source #

Instances

Instances details
SafeToHash ByteString Source # 
Instance details

Defined in Cardano.Ledger.Hashes

SafeToHash ShortByteString Source # 
Instance details

Defined in Cardano.Ledger.Hashes

SafeToHash AnchorData Source # 
Instance details

Defined in Cardano.Ledger.BaseTypes

SafeToHash PlutusBinary Source # 
Instance details

Defined in Cardano.Ledger.Plutus.Language

SafeToHash (SafeHash i) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

SafeToHash (MemoBytes t) Source # 
Instance details

Defined in Cardano.Ledger.MemoBytes.Internal

SafeToHash (BinaryData era) Source # 
Instance details

Defined in Cardano.Ledger.Plutus.Data

SafeToHash (Data era) Source # 
Instance details

Defined in Cardano.Ledger.Plutus.Data

SafeToHash (Plutus l) Source # 
Instance details

Defined in Cardano.Ledger.Plutus.Language

HashAlgorithm h ⇒ SafeToHash (Hash h i) Source #

Hash of a hash. Hash is always safe to hash. Do you even hash?

Instance details

Defined in Cardano.Ledger.Hashes

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.

newtype TxAuxDataHash Source #

Instances

Instances details
ToJSON TxAuxDataHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

DecCBOR TxAuxDataHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

EncCBOR TxAuxDataHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

NFData TxAuxDataHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

rnfTxAuxDataHash → () #

Generic TxAuxDataHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Associated Types

type Rep TxAuxDataHash 
Instance details

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))))
Show TxAuxDataHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Eq TxAuxDataHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Ord TxAuxDataHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

NoThunks TxAuxDataHash Source # 
Instance details

Defined in Cardano.Ledger.Hashes

type Rep TxAuxDataHash Source # 
Instance details

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))))

newtype VRFVerKeyHash (r ∷ KeyRoleVRF) Source #

Discriminated hash of VRF Verification Key

Instances

Instances details
FromJSON (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

FromJSONKey (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSON (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSONKey (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable r ⇒ FromCBOR (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable r ⇒ ToCBOR (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

toCBORVRFVerKeyHash 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 # 
Instance details

Defined in Cardano.Ledger.Hashes

EncCBOR (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Default (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

defVRFVerKeyHash r Source #

NFData (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

rnfVRFVerKeyHash r → () #

Generic (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Associated Types

type Rep (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

fromVRFVerKeyHash r → Rep (VRFVerKeyHash r) x #

toRep (VRFVerKeyHash r) x → VRFVerKeyHash r #

Show (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Eq (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

(==)VRFVerKeyHash r → VRFVerKeyHash r → Bool #

(/=)VRFVerKeyHash r → VRFVerKeyHash r → Bool #

Ord (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

NoThunks (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

type Rep (VRFVerKeyHash r) Source # 
Instance details

Defined in Cardano.Ledger.Hashes

newtype HashHeader Source #

Instances

Instances details
DecCBOR HashHeader Source # 
Instance details

Defined in Cardano.Ledger.Hashes

EncCBOR HashHeader Source # 
Instance details

Defined in Cardano.Ledger.Hashes

NFData HashHeader Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

rnfHashHeader → () #

Generic HashHeader Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Associated Types

type Rep HashHeader 
Instance details

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))))
Show HashHeader Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Eq HashHeader Source # 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

(==)HashHeaderHashHeaderBool #

(/=)HashHeaderHashHeaderBool #

Ord HashHeader Source # 
Instance details

Defined in Cardano.Ledger.Hashes

NoThunks HashHeader Source # 
Instance details

Defined in Cardano.Ledger.Hashes

type Rep HashHeader Source # 
Instance details

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))))

castSafeHashSafeHash i → SafeHash j Source #

To change the index parameter of SafeHash (which is a phantom type) use castSafeHash

extractHashSafeHash i → Hash HASH i Source #

Extract the hash out of a SafeHash

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 #

Methods

upgradeTxCertTxCert (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.

getVKeyWitnessTxCertTxCert era → Maybe (KeyHash 'Witness) Source #

Return a witness key whenever a certificate requires one

getScriptWitnessTxCertTxCert era → Maybe ScriptHash Source #

Return a ScriptHash for certificate types that require a witness

mkRegPoolTxCertStakePoolParamsTxCert era Source #

getRegPoolTxCertTxCert era → Maybe StakePoolParams Source #

mkRetirePoolTxCertKeyHash 'StakePoolEpochNoTxCert era Source #

getRetirePoolTxCertTxCert era → Maybe (KeyHash 'StakePool, EpochNo) Source #

lookupRegStakeTxCertTxCert era → Maybe (Credential 'Staking) Source #

Extract staking credential from any certificate that can register such credential

lookupUnRegStakeTxCertTxCert era → Maybe (Credential 'Staking) Source #

Extract staking credential from any certificate that can unregister such credential

getTotalDepositsTxCerts Source #

Arguments

Foldable f 
PParams era 
→ (KeyHash 'StakePoolBool)

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 'StakingMaybe Coin)

Lookup current deposit for Staking credential if one is registered

→ (Credential 'DRepRoleMaybe Coin)

Lookup current deposit for DRep credential if one is registered

→ f (TxCert era) 
Coin 

Compute the total refunds from a list of certificates.

type family TxCert era = (r ∷ Type) | r → era Source #

data PoolCert Source #

Constructors

RegPool !StakePoolParams

A stake pool registration certificate.

RetirePool !(KeyHash 'StakePool) !EpochNo

A stake pool retirement certificate.

Instances

Instances details
ToJSON PoolCert Source # 
Instance details

Defined in Cardano.Ledger.Core.TxCert

EncCBOR PoolCert Source # 
Instance details

Defined in Cardano.Ledger.Core.TxCert

NFData PoolCert Source # 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

rnfPoolCert → () #

Generic PoolCert Source # 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Associated Types

type Rep PoolCert 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

fromPoolCertRep PoolCert x #

toRep PoolCert x → PoolCert #

Show PoolCert Source # 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

showsPrecIntPoolCertShowS #

showPoolCertString #

showList ∷ [PoolCert] → ShowS #

Eq PoolCert Source # 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

(==)PoolCertPoolCertBool #

(/=)PoolCertPoolCertBool #

Ord PoolCert Source # 
Instance details

Defined in Cardano.Ledger.Core.TxCert

NoThunks PoolCert Source # 
Instance details

Defined in Cardano.Ledger.Core.TxCert

type Rep PoolCert Source # 
Instance details

Defined in Cardano.Ledger.Core.TxCert

isRegStakeTxCertEraTxCert era ⇒ TxCert era → Bool Source #

Check if supplied TxCert is a stake registering certificate

isUnRegStakeTxCertEraTxCert 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 #

Associated Types

type PParamsHKD (f ∷ TypeType) era = (r ∷ Type) | r → era Source #

Protocol parameters where the fields are represented with a HKD

type UpgradePParams (f ∷ TypeType) era Source #

type DowngradePParams (f ∷ TypeType) era Source #

Methods

applyPPUpdatesPParams 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 #

emptyPParamsIdentityPParamsHKD Identity era Source #

emptyPParamsStrictMaybePParamsHKD StrictMaybe era Source #

emptyUpgradePParamsUpdateUpgradePParams StrictMaybe era Source #

upgradePParamsHKD ∷ ∀ (f ∷ TypeType). (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 ∷ TypeType). (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 ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #

The linear factor for the minimum fee calculation

hkdMinFeeBL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #

The constant factor for the minimum fee calculation

hkdMaxBBSizeL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32) Source #

Maximal block body size

hkdMaxTxSizeL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word32) Source #

Maximal transaction size

hkdMaxBHSizeL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16) Source #

Maximal block header size

hkdKeyDepositL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #

The amount of a key registration deposit

hkdPoolDepositCompactL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f (CompactForm Coin)) Source #

The amount of a pool registration deposit

hkdEMaxL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f EpochInterval) Source #

epoch bound on pool retirement

hkdNOptL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Word16) Source #

Desired number of pools

hkdA0L ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f NonNegativeInterval) Source #

Pool influence

hkdRhoL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #

Monetary expansion

hkdTauL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #

Treasury expansion

hkdDL ∷ ∀ (f ∷ TypeType). (HKDFunctor f, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsHKD f era) (HKD f UnitInterval) Source #

Decentralization parameter

ppDGSimpleGetter (PParams era) UnitInterval Source #

Decentralization parameter getter

default ppDGAtMostEra "Alonzo" era ⇒ SimpleGetter (PParams era) UnitInterval Source #

hkdExtraEntropyL ∷ ∀ (f ∷ TypeType). (HKDFunctor f, AtMostEra "Alonzo" era) ⇒ Lens' (PParamsHKD f era) (HKD f Nonce) Source #

Extra entropy

hkdProtocolVersionL ∷ ∀ (f ∷ TypeType). (HKDFunctor f, AtMostEra "Babbage" era) ⇒ Lens' (PParamsHKD f era) (HKD f ProtVer) Source #

Protocol version

ppProtocolVersionLLens' (PParams era) ProtVer Source #

default ppProtocolVersionLAtMostEra "Babbage" era ⇒ Lens' (PParams era) ProtVer Source #

ppuProtocolVersionLLens' (PParamsUpdate era) (StrictMaybe ProtVer) Source #

PParamsUpdate Protocol version

hkdMinUTxOValueL ∷ ∀ (f ∷ TypeType). (HKDFunctor f, AtMostEra "Mary" era) ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #

Minimum UTxO value

hkdMinPoolCostL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f era) (HKD f Coin) Source #

Minimum Stake Pool Cost

eraPParams ∷ [PParam era] Source #

newtype PParams era Source #

Protocol parameters

Constructors

PParams (PParamsHKD Identity era) 

Instances

Instances details
EraPParams era ⇒ FromJSON (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

EraPParams era ⇒ ToJSON (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

EraPParams era ⇒ FromCBOR (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

fromCBORDecoder s (PParams era) Source #

labelProxy (PParams era) → Text Source #

EraPParams era ⇒ ToCBOR (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toCBORPParams era → Encoding Source #

encodedSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy (PParams era) → Size Source #

encodedListSizeExpr ∷ (∀ t. ToCBOR t ⇒ Proxy t → Size) → Proxy [PParams era] → Size Source #

EraPParams era ⇒ DecCBOR (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

decCBORDecoder s (PParams era) Source #

dropCBORProxy (PParams era) → Decoder s () Source #

labelProxy (PParams era) → Text Source #

EraPParams era ⇒ EncCBOR (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

encCBORPParams era → Encoding Source #

EraPParams era ⇒ ToKeyValuePairs (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toKeyValuePairsKeyValue e kv ⇒ PParams era → [kv] Source #

EraPParams era ⇒ Default (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

defPParams era Source #

NFData (PParamsHKD Identity era) ⇒ NFData (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

rnfPParams era → () #

Generic (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Associated Types

type Rep (PParams era) 
Instance details

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 ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD Identity era))))

Methods

fromPParams era → Rep (PParams era) x #

toRep (PParams era) x → PParams era #

Show (PParamsHKD Identity era) ⇒ Show (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

showsPrecIntPParams era → ShowS #

showPParams era → String #

showList ∷ [PParams era] → ShowS #

Eq (PParamsHKD Identity era) ⇒ Eq (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

(==)PParams era → PParams era → Bool #

(/=)PParams era → PParams era → Bool #

Ord (PParamsHKD Identity era) ⇒ Ord (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

comparePParams era → PParams era → Ordering #

(<)PParams era → PParams era → Bool #

(<=)PParams era → PParams era → Bool #

(>)PParams era → PParams era → Bool #

(>=)PParams era → PParams era → Bool #

maxPParams era → PParams era → PParams era #

minPParams era → PParams era → PParams era #

NoThunks (PParamsHKD Identity era) ⇒ NoThunks (PParams era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

type Rep (PParams era) Source # 
Instance details

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 ('NothingMaybe 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.

Constructors

PParam 

Fields

data PParamUpdate era t Source #

Constructors

PParamUpdate 

Fields

newtype PParamsUpdate era Source #

The type of updates to Protocol parameters

Instances

Instances details
EraPParams era ⇒ FromJSON (PParamsUpdate era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

EraPParams era ⇒ ToJSON (PParamsUpdate era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

EraPParams era ⇒ FromCBOR (PParamsUpdate era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

EraPParams era ⇒ ToCBOR (PParamsUpdate era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toCBORPParamsUpdate 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 # 
Instance details

Defined in Cardano.Ledger.Core.PParams

EraPParams era ⇒ EncCBOR (PParamsUpdate era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

EraPParams era ⇒ ToKeyValuePairs (PParamsUpdate era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

toKeyValuePairsKeyValue e kv ⇒ PParamsUpdate era → [kv] Source #

EraPParams era ⇒ Default (PParamsUpdate era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

defPParamsUpdate era Source #

NFData (PParamsHKD StrictMaybe era) ⇒ NFData (PParamsUpdate era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

rnfPParamsUpdate era → () #

Generic (PParamsUpdate era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Associated Types

type Rep (PParamsUpdate era) 
Instance details

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 ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD StrictMaybe era))))

Methods

fromPParamsUpdate era → Rep (PParamsUpdate era) x #

toRep (PParamsUpdate era) x → PParamsUpdate era #

Show (PParamsHKD StrictMaybe era) ⇒ Show (PParamsUpdate era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

showsPrecIntPParamsUpdate era → ShowS #

showPParamsUpdate era → String #

showList ∷ [PParamsUpdate era] → ShowS #

Eq (PParamsHKD StrictMaybe era) ⇒ Eq (PParamsUpdate era) Source # 
Instance details

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 # 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

comparePParamsUpdate era → PParamsUpdate era → Ordering #

(<)PParamsUpdate era → PParamsUpdate era → Bool #

(<=)PParamsUpdate era → PParamsUpdate era → Bool #

(>)PParamsUpdate era → PParamsUpdate era → Bool #

(>=)PParamsUpdate era → PParamsUpdate era → Bool #

maxPParamsUpdate era → PParamsUpdate era → PParamsUpdate era #

minPParamsUpdate era → PParamsUpdate era → PParamsUpdate era #

NoThunks (PParamsHKD StrictMaybe era) ⇒ NoThunks (PParamsUpdate era) Source # 
Instance details

Defined in Cardano.Ledger.Core.PParams

type Rep (PParamsUpdate era) Source # 
Instance details

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 ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD StrictMaybe era))))

ppMinFeeALEraPParams era ⇒ Lens' (PParams era) Coin Source #

The linear factor for the minimum fee calculation

ppMinFeeBLEraPParams era ⇒ Lens' (PParams era) Coin Source #

The constant factor for the minimum fee calculation

ppMaxBBSizeLEraPParams era ⇒ Lens' (PParams era) Word32 Source #

Maximal block body size

ppMaxTxSizeLEraPParams era ⇒ Lens' (PParams era) Word32 Source #

Maximal transaction size

ppMaxBHSizeLEraPParams era ⇒ Lens' (PParams era) Word16 Source #

Maximal block header size

ppKeyDepositLEraPParams 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

ppPoolDepositCompactLEraPParams era ⇒ Lens' (PParams era) (CompactForm Coin) Source #

The amount of a pool registration deposit in compacted form

ppEMaxLEraPParams era ⇒ Lens' (PParams era) EpochInterval Source #

epoch bound on pool retirement

ppNOptLEraPParams era ⇒ Lens' (PParams era) Word16 Source #

Desired number of pools

ppA0LEraPParams era ⇒ Lens' (PParams era) NonNegativeInterval Source #

Pool influence

ppRhoLEraPParams era ⇒ Lens' (PParams era) UnitInterval Source #

Monetary expansion

ppTauLEraPParams 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

ppMinPoolCostLEraPParams era ⇒ Lens' (PParams era) Coin Source #

Minimum Stake Pool Cost

ppuMinFeeALEraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #

The linear factor for the minimum fee calculation

ppuMinFeeBLEraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #

The constant factor for the minimum fee calculation

ppuMaxBBSizeLEraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word32) Source #

Maximal block body size

ppuMaxTxSizeLEraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word32) Source #

Maximal transaction size

ppuMaxBHSizeLEraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word16) Source #

Maximal block header size

ppuKeyDepositLEraPParams 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.

ppuPoolDepositCompactLEraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe (CompactForm Coin)) Source #

The amount of a pool registration deposit in compacted form

ppuEMaxLEraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe EpochInterval) Source #

epoch bound on pool retirement

ppuNOptLEraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe Word16) Source #

Desired number of pools

ppuRhoLEraPParams era ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval) Source #

Monetary expansion

ppuTauLEraPParams 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

ppuMinPoolCostLEraPParams 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 #

type family PParamsHKD (f ∷ TypeType) era = (r ∷ Type) | r → era Source #

Protocol parameters where the fields are represented with a HKD

type family UpgradePParams (f ∷ TypeType) era Source #

type family DowngradePParams (f ∷ TypeType) era Source #

type family PreviousEra era = (r ∷ Type) | r → era Source #

Map an era to its predecessor.

For example:

type instance PreviousEra AllegraEra = ShelleyEra

type family PreviousEra era = (r ∷ Type) | r → era Source #

Map an era to its predecessor.

For example:

type instance PreviousEra AllegraEra = ShelleyEra

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 ∷ TypeType) 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 TxBody

Note: we use PreviousEra instead of NextEra as an era definitely knows its predecessor, but not necessarily its successor. Moreover, one could argue that it makes more sense to define the translation from era A to era B where era B is defined, than where era A is defined.

Minimal complete definition

Nothing

Associated Types

type TranslationError era (f ∷ TypeType) 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 ∷ TypeType) = Void

Methods

translateEraTranslationContext 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 ∷ TypeType) 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.