cardano-ledger-shelley-1.11.0.0: Shelley Ledger Executable Model
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cardano.Ledger.Shelley.Core

Synopsis

Documentation

newtype Withdrawals c Source #

This is called wdrl in the spec.

Constructors

Withdrawals 

Instances

Instances details
Generic (Withdrawals c) 
Instance details

Defined in Cardano.Ledger.Address

Associated Types

type Rep (Withdrawals c) ∷ TypeType Source #

Methods

fromWithdrawals c → Rep (Withdrawals c) x Source #

toRep (Withdrawals c) x → Withdrawals c Source #

Show (Withdrawals c) 
Instance details

Defined in Cardano.Ledger.Address

Crypto c ⇒ DecCBOR (Withdrawals c) 
Instance details

Defined in Cardano.Ledger.Address

Crypto c ⇒ EncCBOR (Withdrawals c) 
Instance details

Defined in Cardano.Ledger.Address

Methods

encCBORWithdrawals c → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (Withdrawals c) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [Withdrawals c] → Size Source #

NFData (Withdrawals c) 
Instance details

Defined in Cardano.Ledger.Address

Methods

rnfWithdrawals c → () Source #

Eq (Withdrawals c) 
Instance details

Defined in Cardano.Ledger.Address

NoThunks (Withdrawals c) 
Instance details

Defined in Cardano.Ledger.Address

type Rep (Withdrawals c) 
Instance details

Defined in Cardano.Ledger.Address

type Rep (Withdrawals c) = D1 ('MetaData "Withdrawals" "Cardano.Ledger.Address" "cardano-ledger-core-1.12.0.0-inplace" 'True) (C1 ('MetaCons "Withdrawals" 'PrefixI 'True) (S1 ('MetaSel ('Just "unWithdrawals") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map (RewardAcnt c) Coin))))

class EraTxCert era ⇒ ShelleyEraTxCert era where Source #

pattern MirTxCert ∷ (ShelleyEraTxCert era, ProtVerAtMost era 8) ⇒ MIRCert (EraCrypto era) → TxCert era Source #

data MIRCert c Source #

Move instantaneous rewards certificate

Constructors

MIRCert 

Fields

Instances

Instances details
Crypto c ⇒ ToJSON (MIRCert c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Generic (MIRCert c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep (MIRCert c) ∷ TypeType Source #

Methods

fromMIRCert c → Rep (MIRCert c) x Source #

toRep (MIRCert c) x → MIRCert c Source #

Show (MIRCert c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

showsPrecIntMIRCert c → ShowS Source #

showMIRCert c → String Source #

showList ∷ [MIRCert c] → ShowS Source #

Crypto c ⇒ DecCBOR (MIRCert c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

decCBORDecoder s (MIRCert c) Source #

dropCBORProxy (MIRCert c) → Decoder s () Source #

labelProxy (MIRCert c) → Text Source #

Crypto c ⇒ EncCBOR (MIRCert c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

encCBORMIRCert c → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (MIRCert c) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [MIRCert c] → Size Source #

NFData (MIRCert c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnfMIRCert c → () Source #

Eq (MIRCert c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

(==)MIRCert c → MIRCert c → Bool Source #

(/=)MIRCert c → MIRCert c → Bool Source #

NoThunks (MIRCert c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep (MIRCert c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep (MIRCert c) = D1 ('MetaData "MIRCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.11.0.0-inplace" 'False) (C1 ('MetaCons "MIRCert" 'PrefixI 'True) (S1 ('MetaSel ('Just "mirPot") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 MIRPot) :*: S1 ('MetaSel ('Just "mirRewards") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (MIRTarget c))))

data MIRPot Source #

Constructors

ReservesMIR 
TreasuryMIR 

Instances

Instances details
ToJSON MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Bounded MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Enum MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Generic MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep MIRPotTypeType Source #

Methods

fromMIRPotRep MIRPot x Source #

toRep MIRPot x → MIRPot Source #

Show MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

DecCBOR MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

EncCBOR MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

encCBORMIRPotEncoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy MIRPotSize Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [MIRPot] → Size Source #

NFData MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnfMIRPot → () Source #

Eq MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

(==)MIRPotMIRPotBool Source #

(/=)MIRPotMIRPotBool Source #

Ord MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

NoThunks MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep MIRPot = D1 ('MetaData "MIRPot" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.11.0.0-inplace" 'False) (C1 ('MetaCons "ReservesMIR" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "TreasuryMIR" 'PrefixI 'False) (U1TypeType))

data MIRTarget c Source #

MIRTarget specifies if funds from either the reserves or the treasury are to be handed out to a collection of reward accounts or instead transfered to the opposite pot.

Instances

Instances details
Crypto c ⇒ ToJSON (MIRTarget c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Generic (MIRTarget c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep (MIRTarget c) ∷ TypeType Source #

Methods

fromMIRTarget c → Rep (MIRTarget c) x Source #

toRep (MIRTarget c) x → MIRTarget c Source #

Show (MIRTarget c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Crypto c ⇒ DecCBOR (MIRTarget c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Crypto c ⇒ EncCBOR (MIRTarget c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

encCBORMIRTarget c → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (MIRTarget c) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [MIRTarget c] → Size Source #

NFData (MIRTarget c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnfMIRTarget c → () Source #

Eq (MIRTarget c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

(==)MIRTarget c → MIRTarget c → Bool Source #

(/=)MIRTarget c → MIRTarget c → Bool Source #

NoThunks (MIRTarget c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep (MIRTarget c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep (MIRTarget c) = D1 ('MetaData "MIRTarget" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.11.0.0-inplace" 'False) (C1 ('MetaCons "StakeAddressesMIR" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (Map (Credential 'Staking c) DeltaCoin))) :+: C1 ('MetaCons "SendToOppositePotMIR" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin)))

txIdTxBodyEraTxBody era ⇒ TxBody era → TxId (EraCrypto era) Source #

txIdTxEraTx era ⇒ Tx era → TxId (EraCrypto era) Source #

bBodySizeEraSegWits era ⇒ ProtVerTxSeq era → Int Source #

hashScriptEraScript era ⇒ Script era → ScriptHash (EraCrypto era) Source #

Compute ScriptHash of a Script for a particular era.

hashScriptTxWitsLEraTxWits era ⇒ Lens (TxWits era) (TxWits era) (Map (ScriptHash (EraCrypto era)) (Script era)) [Script era] Source #

This is a helper lens that will hash the scripts when adding as witnesses.

mkCoinTxOutEraTxOut era ⇒ Addr (EraCrypto era) → CoinTxOut era Source #

isAdaOnlyTxOutFEraTxOut era ⇒ SimpleGetter (TxOut era) Bool Source #

This is a getter that implements an efficient way to check whether TxOut contains ADA only.

type family TxUpgradeError era Source #

Instances

Instances details
type TxUpgradeError (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Tx

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

Instances

Instances details
type Tx (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Tx

class (EraTxBody era, EraTxWits era, EraTxAuxData era, EraPParams era, NoThunks (Tx era), DecCBOR (Annotator (Tx era)), EncCBOR (Tx era), ToCBOR (Tx era), Show (Tx era), Eq (Tx era), EqRaw (Tx era)) ⇒ EraTx era where Source #

A transaction.

Associated Types

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

type TxUpgradeError era Source #

type TxUpgradeError era = Void

Methods

mkBasicTxTxBody era → Tx era Source #

bodyTxLLens' (Tx era) (TxBody era) Source #

witsTxLLens' (Tx era) (TxWits era) Source #

auxDataTxLLens' (Tx era) (StrictMaybe (AuxiliaryData era)) Source #

sizeTxFSimpleGetter (Tx era) Integer Source #

validateNativeScriptTx era → NativeScript era → Bool Source #

Using information from the transaction validate the supplied native script.

getMinFeeTx Source #

Arguments

PParams era 
Tx era 
Int

Size in bytes of reference scripts present in this transaction

Coin 

Minimum fee calculation excluding witnesses

upgradeTxTx (PreviousEra era) → Either (TxUpgradeError era) (Tx era) Source #

type family TxBodyUpgradeError era Source #

Instances

Instances details
type TxBodyUpgradeError (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

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

The body of a transaction.

Instances

Instances details
type TxBody (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

class (EraTxOut era, EraTxCert era, EraPParams era, HashAnnotated (TxBody era) EraIndependentTxBody (EraCrypto era), DecCBOR (Annotator (TxBody era)), EncCBOR (TxBody era), ToCBOR (TxBody era), NoThunks (TxBody era), NFData (TxBody era), Show (TxBody era), Eq (TxBody era), EqRaw (TxBody era)) ⇒ EraTxBody era where Source #

Associated Types

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

The body of a transaction.

type TxBodyUpgradeError era Source #

Methods

mkBasicTxBodyTxBody era Source #

inputsTxBodyLLens' (TxBody era) (Set (TxIn (EraCrypto era))) Source #

outputsTxBodyLLens' (TxBody era) (StrictSeq (TxOut era)) Source #

feeTxBodyLLens' (TxBody era) Coin Source #

withdrawalsTxBodyLLens' (TxBody era) (Withdrawals (EraCrypto era)) Source #

auxDataHashTxBodyLLens' (TxBody era) (StrictMaybe (AuxiliaryDataHash (EraCrypto era))) Source #

spendableInputsTxBodyFSimpleGetter (TxBody era) (Set (TxIn (EraCrypto era))) Source #

This getter will produce all inputs from the UTxO map that this transaction might spend, which ones will depend on the validity of the transaction itself. Starting in Alonzo this will include collateral inputs.

allInputsTxBodyFSimpleGetter (TxBody era) (Set (TxIn (EraCrypto era))) Source #

This getter will produce all inputs from the UTxO map that this transaction is referencing, even if some of them cannot be spent by the transaction. For example starting with Babbage era it will also include reference inputs.

certsTxBodyLLens' (TxBody era) (StrictSeq (TxCert era)) Source #

getTotalDepositsTxBody Source #

Arguments

PParams era 
→ (KeyHash 'StakePool (EraCrypto era) → Bool)

Check whether stake pool is registered or not

TxBody era 
Coin 

Compute the total deposits from the certificates in a TxBody.

This is the contribution of a TxBody towards the consumed amount by the transaction

getTotalRefundsTxBody Source #

Arguments

PParams era 
→ (Credential 'Staking (EraCrypto era) → Maybe Coin)

Lookup current deposit for Staking credential if one is registered

→ (Credential 'DRepRole (EraCrypto era) → Maybe Coin)

Lookup current deposit for DRep credential if one is registered

TxBody era 
Coin 

Compute the total refunds from the Certs of a TxBody.

This is the contribution of a TxBody towards produced amount by the transaction

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

upgradeTxBodyTxBody (PreviousEra era) → Either (TxBodyUpgradeError era) (TxBody era) Source #

Upgrade the transaction body from the previous era.

This can fail where elements of the transaction body are deprecated. Compare this to translateEraThroughCBOR: - upgradeTxBody will use the Haskell representation, but will not preserve the serialised form. However, it will be suitable for iterated translation through eras. - translateEraThroughCBOR will preserve the binary representation, but is not guaranteed to work through multiple eras - that is, the serialised representation from era n is guaranteed valid in era n + 1, but not necessarily in era n + 2.

Instances

Instances details
Crypto c ⇒ EraTxBody (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxBody

Associated Types

type TxBody (ShelleyEra c) = (r ∷ Type) Source #

type TxBodyUpgradeError (ShelleyEra c) Source #

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

The output of a UTxO for a particular era

Instances

Instances details
type TxOut (ShelleyEra crypto) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxOut

type TxOut (ShelleyEra crypto) = ShelleyTxOut (ShelleyEra crypto)

class (Val (Value era), ToJSON (TxOut era), DecCBOR (Value era), DecCBOR (CompactForm (Value era)), EncCBOR (Value era), ToCBOR (TxOut era), FromCBOR (TxOut era), EncCBOR (TxOut era), DecCBOR (TxOut era), DecShareCBOR (TxOut era), Share (TxOut era) ~ Interns (Credential 'Staking (EraCrypto era)), NoThunks (TxOut era), NFData (TxOut era), Show (TxOut era), Eq (TxOut era), EraPParams era) ⇒ EraTxOut era where Source #

Abstract interface into specific fields of a TxOut

Associated Types

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

The output of a UTxO for a particular era

Methods

mkBasicTxOutAddr (EraCrypto era) → Value 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 (EraCrypto era)) Source #

compactAddrTxOutLLens' (TxOut era) (CompactAddr (EraCrypto era)) Source #

addrEitherTxOutLLens' (TxOut era) (Either (Addr (EraCrypto era)) (CompactAddr (EraCrypto era))) Source #

Lens for getting and setting in TxOut either an address or its compact version by doing the least amount of work.

The utility of this function comes from the fact that TxOut usually stores the address in either one of two forms: compacted or unpacked. In order to avoid extroneous conversions in getTxOutAddr and getTxOutCompactAddr we can define just this functionality. Also sometimes it is crucial to know at the callsite which form of address we have readily available without any conversions (eg. searching millions of TxOuts for a particular address)

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.

Instances

Instances details
Crypto crypto ⇒ EraTxOut (ShelleyEra crypto) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxOut

Associated Types

type TxOut (ShelleyEra crypto) = (r ∷ Type) Source #

type family Value era Source #

A value is something which quantifies a transaction output.

Instances

Instances details
type Value (ShelleyEra _c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type Value (ShelleyEra _c) = Coin

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

Instances

Instances details
type TxAuxData (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxAuxData

class (Era era, Eq (TxAuxData era), EqRaw (TxAuxData era), Show (TxAuxData era), NoThunks (TxAuxData era), ToCBOR (TxAuxData era), EncCBOR (TxAuxData era), DecCBOR (Annotator (TxAuxData era)), HashAnnotated (TxAuxData era) EraIndependentTxAuxData (EraCrypto era)) ⇒ EraTxAuxData era where Source #

TxAuxData which may be attached to a transaction

Associated Types

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

Methods

mkBasicTxAuxDataTxAuxData era Source #

metadataTxAuxDataLLens' (TxAuxData era) (Map Word64 Metadatum) Source #

upgradeTxAuxDataTxAuxData (PreviousEra era) → TxAuxData era Source #

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

Warning - Important to note that any memoized binary representation will not be preserved. If you need to retain underlying bytes you can use translateEraThroughCBOR

hashTxAuxDataTxAuxData era → AuxiliaryDataHash (EraCrypto era) Source #

validateTxAuxDataProtVerTxAuxData era → Bool Source #

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

Instances

Instances details
type TxWits (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxWits

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

Associated Types

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

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

Instances

Instances details
type NativeScript (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Scripts

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

Scripts which may lock transaction outputs in this era

Instances

Instances details
type Script (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Scripts

class (Era era, Show (Script era), Eq (Script era), EqRaw (Script era), ToCBOR (Script era), EncCBOR (Script era), DecCBOR (Annotator (Script era)), NoThunks (Script era), SafeToHash (Script era), Eq (NativeScript era), Show (NativeScript era), NFData (NativeScript era), NoThunks (NativeScript era), EncCBOR (NativeScript era), DecCBOR (Annotator (NativeScript era))) ⇒ EraScript era where Source #

Typeclass for script data types. Allows for script validation and hashing. You must understand the role of SafeToHash and scriptPrefixTag to make new instances. scriptPrefixTag is a magic number representing the tag of the script language. For each new script language defined, a new tag is chosen and the tag is included in the script hash for a script. The safeToHash constraint ensures that Scripts are never reserialised.

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, you need to retain underlying bytes you can use translateEraThroughCBOR

scriptPrefixTagScript era → ByteString Source #

getNativeScriptScript era → Maybe (NativeScript era) Source #

fromNativeScriptNativeScript era → Script era Source #

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

Instances

Instances details
type TxSeq (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.BlockChain

class (EraTx era, Eq (TxSeq era), Show (TxSeq era), EncCBORGroup (TxSeq era), DecCBOR (Annotator (TxSeq era))) ⇒ EraSegWits era where Source #

Indicates that an era supports segregated witnessing.

This class embodies an isomorphism between 'TxSeq era' and 'StrictSeq (Tx era)', witnessed by fromTxSeq and toTxSeq.

Associated Types

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

Methods

fromTxSeqTxSeq era → StrictSeq (Tx era) Source #

toTxSeqStrictSeq (Tx era) → TxSeq era Source #

hashTxSeqTxSeq era → Hash (HASH (EraCrypto era)) EraIndependentBlockBody Source #

Get the block body hash from the TxSeq. Note that this is not a regular "hash the stored bytes" function since the block body hash forms a small Merkle tree.

numSegComponentsWord64 Source #

The number of segregated components

Instances

Instances details
Crypto c ⇒ EraSegWits (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.BlockChain

Associated Types

type TxSeq (ShelleyEra c) = (r ∷ Type) Source #

isUnRegStakeTxCertEraTxCert era ⇒ TxCert era → Bool Source #

Check if supplied TxCert is a stake un-registering certificate

isRegStakeTxCertEraTxCert era ⇒ TxCert era → Bool Source #

Check if supplied TxCert is a stake registering certificate

pattern RegPoolTxCertEraTxCert era ⇒ PoolParams (EraCrypto era) → TxCert era Source #

pattern RetirePoolTxCertEraTxCert era ⇒ KeyHash 'StakePool (EraCrypto era) → EpochNoTxCert era Source #

type family TxCertUpgradeError era Source #

Instances

Instances details
type TxCertUpgradeError (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

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

Instances

Instances details
type TxCert (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

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), 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 (EraCrypto era)) Source #

Return a witness key whenever a certificate requires one

getScriptWitnessTxCertTxCert era → Maybe (ScriptHash (EraCrypto era)) Source #

Return a ScriptHash for certificate types that require a witness

mkRegPoolTxCertPoolParams (EraCrypto era) → TxCert era Source #

getRegPoolTxCertTxCert era → Maybe (PoolParams (EraCrypto era)) Source #

mkRetirePoolTxCertKeyHash 'StakePool (EraCrypto era) → EpochNoTxCert era Source #

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

lookupRegStakeTxCertTxCert era → Maybe (Credential 'Staking (EraCrypto era)) Source #

Extract staking credential from any certificate that can register such credential

lookupUnRegStakeTxCertTxCert era → Maybe (Credential 'Staking (EraCrypto era)) Source #

Extract staking credential from any certificate that can unregister such credential

getTotalDepositsTxCerts Source #

Arguments

Foldable f 
PParams era 
→ (KeyHash 'StakePool (EraCrypto era) → Bool)

Check whether stake pool is registered or not

→ f (TxCert era) 
Coin 

Compute the total deposits from a list of certificates.

getTotalRefundsTxCerts Source #

Arguments

Foldable f 
PParams era 
→ (Credential 'Staking (EraCrypto era) → Maybe Coin)

Lookup current deposit for Staking credential if one is registered

→ (Credential 'DRepRole (EraCrypto era) → Maybe Coin)

Lookup current deposit for DRep credential if one is registered

→ f (TxCert era) 
Coin 

Compute the total refunds from a list of certificates.

Instances

Instances details
Crypto c ⇒ EraTxCert (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type TxCert (ShelleyEra c) = (r ∷ Type) Source #

type TxCertUpgradeError (ShelleyEra c) Source #

data Delegation c Source #

The delegation of one stake key to another.

Constructors

Delegation 

Instances

Instances details
Generic (Delegation c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Associated Types

type Rep (Delegation c) ∷ TypeType Source #

Methods

fromDelegation c → Rep (Delegation c) x Source #

toRep (Delegation c) x → Delegation c Source #

Show (Delegation c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

NFData (Delegation c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

rnfDelegation c → () Source #

Eq (Delegation c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

(==)Delegation c → Delegation c → Bool Source #

(/=)Delegation c → Delegation c → Bool Source #

NoThunks (Delegation c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

type Rep (Delegation c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

type Rep (Delegation c) = D1 ('MetaData "Delegation" "Cardano.Ledger.Core.TxCert" "cardano-ledger-core-1.12.0.0-inplace" 'False) (C1 ('MetaCons "Delegation" 'PrefixI 'True) (S1 ('MetaSel ('Just "dDelegator") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (StakeCredential c)) :*: S1 ('MetaSel ('Just "dDelegatee") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c))))

data PoolCert c Source #

Constructors

RegPool !(PoolParams c)

A stake pool registration certificate.

RetirePool !(KeyHash 'StakePool c) !EpochNo

A stake pool retirement certificate.

Instances

Instances details
Crypto c ⇒ ToJSON (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Generic (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Associated Types

type Rep (PoolCert c) ∷ TypeType Source #

Methods

fromPoolCert c → Rep (PoolCert c) x Source #

toRep (PoolCert c) x → PoolCert c Source #

Show (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

NFData (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

rnfPoolCert c → () Source #

Eq (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

(==)PoolCert c → PoolCert c → Bool Source #

(/=)PoolCert c → PoolCert c → Bool Source #

Ord (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

comparePoolCert c → PoolCert c → Ordering Source #

(<)PoolCert c → PoolCert c → Bool Source #

(<=)PoolCert c → PoolCert c → Bool Source #

(>)PoolCert c → PoolCert c → Bool Source #

(>=)PoolCert c → PoolCert c → Bool Source #

maxPoolCert c → PoolCert c → PoolCert c Source #

minPoolCert c → PoolCert c → PoolCert c Source #

NoThunks (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

type Rep (PoolCert c) 
Instance details

Defined in Cardano.Ledger.Core.TxCert

type Rep (PoolCert c) = D1 ('MetaData "PoolCert" "Cardano.Ledger.Core.TxCert" "cardano-ledger-core-1.12.0.0-inplace" 'False) (C1 ('MetaCons "RegPool" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (PoolParams c))) :+: C1 ('MetaCons "RetirePool" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (KeyHash 'StakePool c)) :*: S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 EpochNo)))

makePParamMap ∷ [PParam era] → Map Word (PParam era) Source #

Turn a list into a Map, this assures we have no duplicates.

mapPParams ∷ (PParamsHKD Identity era1 → PParamsHKD Identity era2) → PParams era1 → PParams era2 Source #

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

Minimum Stake Pool Cost

ppuMinUTxOValueL ∷ (EraPParams era, ProtVerAtMost era 4) ⇒ Lens' (PParamsUpdate era) (StrictMaybe Coin) Source #

Minimum UTxO value

ppuDL ∷ (EraPParams era, ProtVerAtMost era 6) ⇒ Lens' (PParamsUpdate era) (StrictMaybe UnitInterval) Source #

Decentralization parameter

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

Treasury expansion

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

Monetary expansion

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

Desired number of pools

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

epoch bound on pool retirement

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

The amount of a pool registration deposit

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

The amount of a key registration deposit

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

Maximal block header size

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

Maximal transaction size

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

Maximal block body size

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

The constant factor for the minimum fee calculation

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

The linear factor for the minimum fee calculation

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

Minimum Stake Pool Cost

ppMinUTxOValueL ∷ (EraPParams era, ProtVerAtMost era 4) ⇒ Lens' (PParams era) Coin Source #

Minimum UTxO value

ppExtraEntropyL ∷ (EraPParams era, ProtVerAtMost era 6) ⇒ Lens' (PParams era) Nonce Source #

Extra entropy

ppDL ∷ (EraPParams era, ProtVerAtMost era 6) ⇒ Lens' (PParams era) UnitInterval Source #

Decentralization parameter

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

Treasury expansion

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

Monetary expansion

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

Pool influence

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

Desired number of pools

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

epoch bound on pool retirement

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

The amount of a pool registration deposit

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

The amount of a key registration deposit

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

Maximal block header size

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

Maximal transaction size

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

Maximal block body size

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

The constant factor for the minimum fee calculation

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

The linear factor for the minimum fee calculation

newtype PParams era Source #

Protocol parameters

Constructors

PParams (PParamsHKD Identity era) 

Instances

Instances details
FromJSON (PParamsHKD Identity era) ⇒ FromJSON (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

ToJSON (PParamsHKD Identity era) ⇒ ToJSON (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Generic (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Associated Types

type Rep (PParams era) ∷ TypeType Source #

Methods

fromPParams era → Rep (PParams era) x Source #

toRep (PParams era) x → PParams era Source #

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

Defined in Cardano.Ledger.Core.PParams

Methods

showsPrecIntPParams era → ShowS Source #

showPParams era → String Source #

showList ∷ [PParams era] → ShowS Source #

(Typeable era, FromCBOR (PParamsHKD Identity era)) ⇒ FromCBOR (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

fromCBORDecoder s (PParams era) Source #

labelProxy (PParams era) → Text Source #

(Typeable era, ToCBOR (PParamsHKD Identity era)) ⇒ ToCBOR (PParams era) 
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 #

(Typeable era, DecCBOR (PParamsHKD Identity era)) ⇒ DecCBOR (PParams era) 
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 #

(Typeable era, EncCBOR (PParamsHKD Identity era)) ⇒ EncCBOR (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

encCBORPParams era → Encoding Source #

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

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

EraPParams era ⇒ Default (PParams era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

defPParams era Source #

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

Defined in Cardano.Ledger.Core.PParams

Methods

rnfPParams era → () Source #

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

Defined in Cardano.Ledger.Core.PParams

Methods

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

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

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

Defined in Cardano.Ledger.Core.PParams

Methods

comparePParams era → PParams era → Ordering Source #

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

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

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

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

maxPParams era → PParams era → PParams era Source #

minPParams era → PParams era → PParams era Source #

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

Defined in Cardano.Ledger.Core.PParams

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.12.0.0-inplace" 'True) (C1 ('MetaCons "PParams" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD Identity era))))

newtype PParamsUpdate era Source #

The type of updates to Protocol parameters

Instances

Instances details
FromJSON (PParamsHKD StrictMaybe era) ⇒ FromJSON (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

ToJSON (PParamsHKD StrictMaybe era) ⇒ ToJSON (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Generic (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Associated Types

type Rep (PParamsUpdate era) ∷ TypeType Source #

Methods

fromPParamsUpdate era → Rep (PParamsUpdate era) x Source #

toRep (PParamsUpdate era) x → PParamsUpdate era Source #

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

Defined in Cardano.Ledger.Core.PParams

(Typeable era, FromCBOR (PParamsHKD StrictMaybe era)) ⇒ FromCBOR (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

(Typeable era, ToCBOR (PParamsHKD StrictMaybe era)) ⇒ ToCBOR (PParamsUpdate era) 
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 #

(Typeable era, DecCBOR (PParamsHKD StrictMaybe era)) ⇒ DecCBOR (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

(Typeable era, EncCBOR (PParamsHKD StrictMaybe era)) ⇒ EncCBOR (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

encCBORPParamsUpdate era → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (PParamsUpdate era) → Size Source #

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

EraPParams era ⇒ Default (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

Methods

defPParamsUpdate era Source #

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

Defined in Cardano.Ledger.Core.PParams

Methods

rnfPParamsUpdate era → () Source #

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

Defined in Cardano.Ledger.Core.PParams

Methods

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

(/=)PParamsUpdate era → PParamsUpdate era → Bool Source #

Ord (PParamsHKD StrictMaybe era) ⇒ Ord (PParamsUpdate era) 
Instance details

Defined in Cardano.Ledger.Core.PParams

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

Defined in Cardano.Ledger.Core.PParams

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.12.0.0-inplace" 'True) (C1 ('MetaCons "PParamsUpdate" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PParamsHKD StrictMaybe era))))

type family DowngradePParams (f ∷ TypeType) era Source #

Instances

Instances details
type DowngradePParams f (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

type family UpgradePParams (f ∷ TypeType) era Source #

 

Instances

Instances details
type UpgradePParams f (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

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

Protocol parameters where the fields are represented with a HKD

Instances

Instances details
type PParamsHKD f (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

class (Era era, Eq (PParamsHKD Identity era), Ord (PParamsHKD Identity era), Show (PParamsHKD Identity era), NFData (PParamsHKD Identity era), EncCBOR (PParamsHKD Identity era), DecCBOR (PParamsHKD Identity era), ToCBOR (PParamsHKD Identity era), FromCBOR (PParamsHKD Identity era), NoThunks (PParamsHKD Identity era), ToJSON (PParamsHKD Identity era), FromJSON (PParamsHKD Identity era), Eq (PParamsHKD StrictMaybe era), Ord (PParamsHKD StrictMaybe era), Show (PParamsHKD StrictMaybe era), NFData (PParamsHKD StrictMaybe era), EncCBOR (PParamsHKD StrictMaybe era), DecCBOR (PParamsHKD StrictMaybe era), ToCBOR (PParamsHKD StrictMaybe era), FromCBOR (PParamsHKD StrictMaybe era), NoThunks (PParamsHKD StrictMaybe era), ToJSON (PParamsHKD StrictMaybe era)) ⇒ EraPParams era where Source #

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

ppDGSimpleGetter (PParams era) UnitInterval Source #

Decentralization parameter getter

ppProtocolVersionLLens' (PParams era) ProtVer Source #

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

PParamsUpdate Protocol version

Instances

Instances details
Crypto c ⇒ EraPParams (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Associated Types

type PParamsHKD f (ShelleyEra c) = (r ∷ Type) Source #

type UpgradePParams f (ShelleyEra c) Source #

type DowngradePParams f (ShelleyEra c) Source #

Methods

applyPPUpdatesPParams (ShelleyEra c) → PParamsUpdate (ShelleyEra c) → PParams (ShelleyEra c) Source #

emptyPParamsIdentityPParamsHKD Identity (ShelleyEra c) Source #

emptyPParamsStrictMaybePParamsHKD StrictMaybe (ShelleyEra c) Source #

upgradePParamsHKD ∷ ∀ (f ∷ TypeType). (HKDApplicative f, EraPParams (PreviousEra (ShelleyEra c))) ⇒ UpgradePParams f (ShelleyEra c) → PParamsHKD f (PreviousEra (ShelleyEra c)) → PParamsHKD f (ShelleyEra c) Source #

downgradePParamsHKD ∷ ∀ (f ∷ TypeType). (HKDFunctor f, EraPParams (PreviousEra (ShelleyEra c))) ⇒ DowngradePParams f (ShelleyEra c) → PParamsHKD f (ShelleyEra c) → PParamsHKD f (PreviousEra (ShelleyEra c)) Source #

hkdMinFeeAL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f (ShelleyEra c)) (HKD f Coin) Source #

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

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

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

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

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

hkdPoolDepositL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f (ShelleyEra c)) (HKD f Coin) Source #

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

hkdNOptL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f (ShelleyEra c)) (HKD f Natural) Source #

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

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

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

hkdDL ∷ ∀ (f ∷ TypeType). (HKDFunctor f, ProtVerAtMost (ShelleyEra c) 6) ⇒ Lens' (PParamsHKD f (ShelleyEra c)) (HKD f UnitInterval) Source #

ppDGSimpleGetter (PParams (ShelleyEra c)) UnitInterval Source #

hkdExtraEntropyL ∷ ∀ (f ∷ TypeType). (HKDFunctor f, ProtVerAtMost (ShelleyEra c) 6) ⇒ Lens' (PParamsHKD f (ShelleyEra c)) (HKD f Nonce) Source #

hkdProtocolVersionL ∷ ∀ (f ∷ TypeType). (HKDFunctor f, ProtVerAtMost (ShelleyEra c) 8) ⇒ Lens' (PParamsHKD f (ShelleyEra c)) (HKD f ProtVer) Source #

ppProtocolVersionLLens' (PParams (ShelleyEra c)) ProtVer Source #

ppuProtocolVersionLLens' (PParamsUpdate (ShelleyEra c)) (StrictMaybe ProtVer) Source #

hkdMinUTxOValueL ∷ ∀ (f ∷ TypeType). (HKDFunctor f, ProtVerAtMost (ShelleyEra c) 4) ⇒ Lens' (PParamsHKD f (ShelleyEra c)) (HKD f Coin) Source #

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

data PParam era where Source #

Pair the tag, and exisitenially hide the type of the lens for the field with that Lens'

Constructors

PParam ∷ ∀ t era. ToPlutusData t ⇒ WordLens' (PParamsUpdate era) (StrictMaybe t) → PParam era 

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

Defined in Cardano.Ledger.Rewards

Bounded RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

Enum RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

Generic RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

Associated Types

type Rep RewardTypeTypeType Source #

Show RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

DecCBOR RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

EncCBOR RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

encCBORRewardTypeEncoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy RewardTypeSize Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [RewardType] → Size Source #

NFData RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

rnfRewardType → () Source #

Eq RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

Ord RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

NoThunks RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

type Rep RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

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

data Reward c 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
Crypto c ⇒ ToJSON (Reward c) 
Instance details

Defined in Cardano.Ledger.Rewards

Generic (Reward c) 
Instance details

Defined in Cardano.Ledger.Rewards

Associated Types

type Rep (Reward c) ∷ TypeType Source #

Methods

fromReward c → Rep (Reward c) x Source #

toRep (Reward c) x → Reward c Source #

Show (Reward c) 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

showsPrecIntReward c → ShowS Source #

showReward c → String Source #

showList ∷ [Reward c] → ShowS Source #

Crypto c ⇒ DecCBOR (Reward c) 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

decCBORDecoder s (Reward c) Source #

dropCBORProxy (Reward c) → Decoder s () Source #

labelProxy (Reward c) → Text Source #

Crypto c ⇒ EncCBOR (Reward c) 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

encCBORReward c → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (Reward c) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [Reward c] → Size Source #

NFData (Reward c) 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

rnfReward c → () Source #

Eq (Reward c) 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

(==)Reward c → Reward c → Bool Source #

(/=)Reward c → Reward c → Bool Source #

Ord (Reward c)

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

compareReward c → Reward c → Ordering Source #

(<)Reward c → Reward c → Bool Source #

(<=)Reward c → Reward c → Bool Source #

(>)Reward c → Reward c → Bool Source #

(>=)Reward c → Reward c → Bool Source #

maxReward c → Reward c → Reward c Source #

minReward c → Reward c → Reward c Source #

NoThunks (Reward c) 
Instance details

Defined in Cardano.Ledger.Rewards

type Rep (Reward c) 
Instance details

Defined in Cardano.Ledger.Rewards

type Rep (Reward c) = D1 ('MetaData "Reward" "Cardano.Ledger.Rewards" "cardano-ledger-core-1.12.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 c)) :*: S1 ('MetaSel ('Just "rewardAmount") 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Coin))))

newtype ScriptHash c Source #

Instances

Instances details
Crypto c ⇒ FromJSON (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Crypto c ⇒ FromJSONKey (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Crypto c ⇒ ToJSON (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Crypto c ⇒ ToJSONKey (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Generic (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Associated Types

type Rep (ScriptHash c) ∷ TypeType Source #

Methods

fromScriptHash c → Rep (ScriptHash c) x Source #

toRep (ScriptHash c) x → ScriptHash c Source #

Show (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Crypto c ⇒ FromCBOR (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Crypto c ⇒ ToCBOR (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

toCBORScriptHash c → Encoding Source #

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

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

Crypto c ⇒ DecCBOR (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Crypto c ⇒ EncCBOR (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

encCBORScriptHash c → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (ScriptHash c) → Size Source #

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

NFData (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

rnfScriptHash c → () Source #

Eq (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

(==)ScriptHash c → ScriptHash c → Bool Source #

(/=)ScriptHash c → ScriptHash c → Bool Source #

Ord (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

NoThunks (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

type Rep (ScriptHash c) 
Instance details

Defined in Cardano.Ledger.Hashes

type Rep (ScriptHash c) = D1 ('MetaData "ScriptHash" "Cardano.Ledger.Hashes" "cardano-ledger-core-1.12.0.0-inplace" 'True) (C1 ('MetaCons "ScriptHash" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Hash (ADDRHASH c) EraIndependentScript))))

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.

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.

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

Instances

Instances details
type TranslationContext (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Translation

type family TranslationError era (f ∷ TypeTYPE LiftedRep) Source #

Most translations should be infallible (default instance), but we leave the door open for partial translations.

For a partial translation, override the default type to be () or a concrete error type.

class (Era era, Era (PreviousEra era)) ⇒ TranslateEra era (f ∷ TypeTYPE LiftedRep) 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 (Allegra c) Foo

Note that one could use DerivingAnyClass (deriving (TranslateEra (Allegra c))), but this would introduce an undesired coupling between the era-parametric type and (a) particular era(s). The intention is to have a module with orphan instances per era.

In most cases, the era parameter won't be phantom, and a manual instance will have to be written:

newtype Bar era = Bar (TxBody era)

instance CC.Crypto c => TranslateEra (Allegra c) Bar where
    translateEra ctxt = Bar <$> translateEra ctxt

-- With the following instance being in scope:
instance CC.Crypto c => TranslatEra (Allegra c) TxBody

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

Minimal complete definition

Nothing

Associated Types

type TranslationError era (f ∷ TypeTYPE LiftedRep) 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 LiftedRep) = 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.

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

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

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

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

atMostEra ∷ ∀ (eraName ∷ TypeType) 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 StandardCrypto)
>>> atMostEra @AlonzoEra @(MaryEra StandardCrypto)

However this will result in a type error

>>> atMostEra @BabbageEra @(ConwayEra StandardCrypto)

atLeastEra ∷ ∀ (eraName ∷ TypeType) 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 @BabbageEra @(ConwayEra StandardCrypto)
>>> atLeastEra @BabbageEra @(BabbageEra StandardCrypto)

However this will result in a type error

>>> atLeastEra @BabbageEra @(AlonzoEra StandardCrypto)

eraProtVerHighEra era ⇒ Version Source #

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

eraProtVerLowEra era ⇒ Version Source #

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

absurdEraRule ∷ ∀ (rule ∷ Symbol) era a. VoidEraRule rule era → a Source #

type family ProtVerHigh era ∷ Nat Source #

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

Instances

Instances details
type ProtVerHigh (ByronEra c) 
Instance details

Defined in Cardano.Ledger.Core.Era

type ProtVerHigh (ByronEra c) = 1
type ProtVerHigh (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type family ProtVerLow era ∷ Nat Source #

Lowest major protocol version for this era

Instances

Instances details
type ProtVerLow (ByronEra c) 
Instance details

Defined in Cardano.Ledger.Core.Era

type ProtVerLow (ByronEra c) = 0
type ProtVerLow (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type ProtVerLow (ShelleyEra c) = 2

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

Map an era to its predecessor.

For example:

type instance PreviousEra (AllegraEra c) = ShelleyEra c

Instances

Instances details
type PreviousEra (ByronEra c) 
Instance details

Defined in Cardano.Ledger.Core.Era

type PreviousEra (ByronEra c) = VoidEra c
type PreviousEra (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type family EraCrypto era Source #

Instances

Instances details
type EraCrypto (ByronEra c) 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraCrypto (ByronEra c) = c
type EraCrypto (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraCrypto (ShelleyEra c) = c

class (Crypto (EraCrypto era), Typeable era, KnownNat (ProtVerLow era), KnownNat (ProtVerHigh era), ProtVerLow era <= ProtVerHigh era, MinVersion <= ProtVerLow era, MinVersion <= ProtVerHigh era, CmpNat (ProtVerLow era) MaxVersion ~ 'LT, CmpNat (ProtVerHigh era) MaxVersion ~ 'LT, ProtVerLow era <= MaxVersion, ProtVerHigh era <= MaxVersion) ⇒ Era era where Source #

Associated Types

type EraCrypto era Source #

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

Map an era to its predecessor.

For example:

type instance PreviousEra (AllegraEra c) = ShelleyEra c

type ProtVerLow era ∷ Nat Source #

Lowest major protocol version for this era

type ProtVerHigh era ∷ Nat Source #

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

type ProtVerHigh era = ProtVerLow era

Methods

eraNameString Source #

Textual name of the current era.

Designed to be used with TypeApplications:

>>> eraName @(ByronEra StandardCrypto)
Byron

Instances

Instances details
Crypto c ⇒ Era (ByronEra c) 
Instance details

Defined in Cardano.Ledger.Core.Era

Associated Types

type EraCrypto (ByronEra c) Source #

type PreviousEra (ByronEra c) = (r ∷ Type) Source #

type ProtVerLow (ByronEra c) ∷ Nat Source #

type ProtVerHigh (ByronEra c) ∷ Nat Source #

Methods

eraNameString Source #

Crypto c ⇒ Era (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

Associated Types

type EraCrypto (ShelleyEra c) Source #

type PreviousEra (ShelleyEra c) = (r ∷ Type) Source #

type ProtVerLow (ShelleyEra c) ∷ Nat Source #

type ProtVerHigh (ShelleyEra c) ∷ Nat Source #

Methods

eraNameString Source #

data ByronEra c Source #

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

Instances

Instances details
Crypto c ⇒ Era (ByronEra c) 
Instance details

Defined in Cardano.Ledger.Core.Era

Associated Types

type EraCrypto (ByronEra c) Source #

type PreviousEra (ByronEra c) = (r ∷ Type) Source #

type ProtVerLow (ByronEra c) ∷ Nat Source #

type ProtVerHigh (ByronEra c) ∷ Nat Source #

Methods

eraNameString Source #

type EraCrypto (ByronEra c) 
Instance details

Defined in Cardano.Ledger.Core.Era

type EraCrypto (ByronEra c) = c
type PreviousEra (ByronEra c) 
Instance details

Defined in Cardano.Ledger.Core.Era

type PreviousEra (ByronEra c) = VoidEra c
type ProtVerHigh (ByronEra c) 
Instance details

Defined in Cardano.Ledger.Core.Era

type ProtVerHigh (ByronEra c) = 1
type ProtVerLow (ByronEra c) 
Instance details

Defined in Cardano.Ledger.Core.Era

type ProtVerLow (ByronEra c) = 0

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

Era STS map

Instances

Instances details
type EraRule "BBODY" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "BBODY" (ShelleyEra c) = ShelleyBBODY (ShelleyEra c)
type EraRule "DELEG" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "DELEG" (ShelleyEra c) = ShelleyDELEG (ShelleyEra c)
type EraRule "DELEGS" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "DELEGS" (ShelleyEra c) = ShelleyDELEGS (ShelleyEra c)
type EraRule "DELPL" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "DELPL" (ShelleyEra c) = ShelleyDELPL (ShelleyEra c)
type EraRule "EPOCH" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "EPOCH" (ShelleyEra c) = ShelleyEPOCH (ShelleyEra c)
type EraRule "LEDGER" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "LEDGER" (ShelleyEra c) = ShelleyLEDGER (ShelleyEra c)
type EraRule "LEDGERS" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "LEDGERS" (ShelleyEra c) = ShelleyLEDGERS (ShelleyEra c)
type EraRule "MIR" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "NEWEPOCH" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "NEWEPOCH" (ShelleyEra c) = ShelleyNEWEPOCH (ShelleyEra c)
type EraRule "NEWPP" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "NEWPP" (ShelleyEra c) = ShelleyNEWPP (ShelleyEra c)
type EraRule "POOL" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "POOLREAP" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "POOLREAP" (ShelleyEra c) = ShelleyPOOLREAP (ShelleyEra c)
type EraRule "PPUP" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "RUPD" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "SNAP" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "TICK" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "TICKF" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "TICKF" (ShelleyEra c) = ShelleyTICKF (ShelleyEra c)
type EraRule "UPEC" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "UTXO" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "UTXOW" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

type EraRule "UTXOW" (ShelleyEra c) = ShelleyUTXOW (ShelleyEra c)

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

Defined in Cardano.Ledger.Core.Era

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

Defined in Cardano.Ledger.Core.Era

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

Defined in Cardano.Ledger.Core.Era

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

Defined in Cardano.Ledger.Core.Era

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

Defined in Cardano.Ledger.Core.Era

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

Defined in Cardano.Ledger.Core.Era

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

Defined in Cardano.Ledger.Core.Era

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

Defined in Cardano.Ledger.Core.Era

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

Defined in Cardano.Ledger.Core.Era

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

Defined in Cardano.Ledger.Core.Era

type EraRuleFailure "UPEC" era = VoidEraRule "UPEC" era
type EraRuleFailure "BBODY" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

type EraRuleFailure "DELEG" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Deleg

type EraRuleFailure "DELEGS" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delegs

type EraRuleFailure "DELPL" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delpl

type EraRuleFailure "LEDGER" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

type EraRuleFailure "LEDGERS" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

type EraRuleFailure "POOL" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Pool

type EraRuleFailure "PPUP" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ppup

type EraRuleFailure "UTXO" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxo

type EraRuleFailure "UTXOW" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxow

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

Instances

Instances details
type EraRuleEvent "LEDGER" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

type EraRuleEvent "LEDGERS" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

type EraRuleEvent "NEWEPOCH" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.NewEpoch

type EraRuleEvent "POOLREAP" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.PoolReap

type EraRuleEvent "TICK" (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Tick

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
Show (VoidEraRule rule era) 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

showsPrecIntVoidEraRule rule era → ShowS Source #

showVoidEraRule rule era → String Source #

showList ∷ [VoidEraRule rule era] → ShowS Source #

(KnownSymbol rule, Era era) ⇒ FromCBOR (VoidEraRule rule era) 
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) 
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) 
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) 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

encCBORVoidEraRule rule era → Encoding Source #

encodedSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy (VoidEraRule rule era) → Size Source #

encodedListSizeExpr ∷ (∀ t. EncCBOR t ⇒ Proxy t → Size) → Proxy [VoidEraRule rule era] → Size Source #

NFData (VoidEraRule rule era) 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

rnfVoidEraRule rule era → () Source #

Eq (VoidEraRule rule era) 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

(==)VoidEraRule rule era → VoidEraRule rule era → Bool Source #

(/=)VoidEraRule rule era → VoidEraRule rule era → Bool Source #

Ord (VoidEraRule rule era) 
Instance details

Defined in Cardano.Ledger.Core.Era

Methods

compareVoidEraRule rule era → VoidEraRule rule era → Ordering Source #

(<)VoidEraRule rule era → VoidEraRule rule era → Bool Source #

(<=)VoidEraRule rule era → VoidEraRule rule era → Bool Source #

(>)VoidEraRule rule era → VoidEraRule rule era → Bool Source #

(>=)VoidEraRule rule era → VoidEraRule rule era → Bool Source #

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

minVoidEraRule rule era → VoidEraRule rule era → VoidEraRule rule era Source #

class EraRuleFailure rule era ~ PredicateFailure (EraRule rule era) ⇒ InjectRuleFailure (rule ∷ Symbol) (t ∷ TypeTYPE LiftedRep) era where Source #

Minimal complete definition

Nothing

Methods

injectFailure ∷ t era → EraRuleFailure rule era Source #

Instances

Instances details
InjectRuleFailure "BBODY" ShelleyBbodyPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

InjectRuleFailure "BBODY" ShelleyDelegPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

InjectRuleFailure "BBODY" ShelleyDelegsPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

InjectRuleFailure "BBODY" ShelleyDelplPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

InjectRuleFailure "BBODY" ShelleyLedgerPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

InjectRuleFailure "BBODY" ShelleyLedgersPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

InjectRuleFailure "BBODY" ShelleyPoolPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

InjectRuleFailure "BBODY" ShelleyPpupPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

InjectRuleFailure "BBODY" ShelleyUtxoPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

InjectRuleFailure "BBODY" ShelleyUtxowPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Bbody

InjectRuleFailure "DELEG" ShelleyDelegPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Deleg

InjectRuleFailure "DELEGS" ShelleyDelegPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delegs

InjectRuleFailure "DELEGS" ShelleyDelegsPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delegs

InjectRuleFailure "DELEGS" ShelleyDelplPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delegs

InjectRuleFailure "DELEGS" ShelleyPoolPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delegs

InjectRuleFailure "DELPL" ShelleyDelegPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delpl

InjectRuleFailure "DELPL" ShelleyDelplPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delpl

InjectRuleFailure "DELPL" ShelleyPoolPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Delpl

InjectRuleFailure "LEDGER" ShelleyDelegPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

InjectRuleFailure "LEDGER" ShelleyDelegsPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

InjectRuleFailure "LEDGER" ShelleyDelplPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

InjectRuleFailure "LEDGER" ShelleyLedgerPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

InjectRuleFailure "LEDGER" ShelleyPoolPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

InjectRuleFailure "LEDGER" ShelleyPpupPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

InjectRuleFailure "LEDGER" ShelleyUtxoPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

InjectRuleFailure "LEDGER" ShelleyUtxowPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledger

InjectRuleFailure "LEDGERS" ShelleyDelegPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

InjectRuleFailure "LEDGERS" ShelleyDelegsPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

InjectRuleFailure "LEDGERS" ShelleyDelplPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

InjectRuleFailure "LEDGERS" ShelleyLedgerPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

InjectRuleFailure "LEDGERS" ShelleyLedgersPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

InjectRuleFailure "LEDGERS" ShelleyPoolPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

InjectRuleFailure "LEDGERS" ShelleyPpupPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

InjectRuleFailure "LEDGERS" ShelleyUtxoPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

InjectRuleFailure "LEDGERS" ShelleyUtxowPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ledgers

InjectRuleFailure "POOL" ShelleyPoolPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Pool

InjectRuleFailure "PPUP" ShelleyPpupPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Ppup

InjectRuleFailure "UTXO" ShelleyPpupPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxo

InjectRuleFailure "UTXO" ShelleyUtxoPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxo

InjectRuleFailure "UTXOW" ShelleyPpupPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxow

InjectRuleFailure "UTXOW" ShelleyUtxoPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxow

InjectRuleFailure "UTXOW" ShelleyUtxowPredFailure (ShelleyEra c) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Rules.Utxow

class EraRuleEvent rule era ~ Event (EraRule rule era) ⇒ InjectRuleEvent (rule ∷ Symbol) (t ∷ TypeTYPE LiftedRep) era where Source #

Minimal complete definition

Nothing

Methods

injectEvent ∷ t era → EraRuleEvent rule era Source #

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

type ExactEra (inEra ∷ TypeType) era = ProtVerInBounds era (ProtVerLow (inEra (EraCrypto era))) (ProtVerHigh (inEra (EraCrypto era))) Source #

Restrict an era to the specific era through the protocol version. This is equivalent to (inEra (Crypto era) ~ era)

type AtLeastEra (eraName ∷ TypeType) era = ProtVerAtLeast era (ProtVerLow (eraName (EraCrypto era))) Source #

Restrict the era to equal to eraName or come after it

type AtMostEra (eraName ∷ TypeType) era = ProtVerAtMost era (ProtVerHigh (eraName (EraCrypto era))) Source #

Restrict the era to equal to eraName or come before it.