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

Cardano.Ledger.Shelley.Core

Synopsis

Documentation

newtype Withdrawals Source #

This is called wdrl in the spec.

Instances

Instances details
Generic Withdrawals 
Instance details

Defined in Cardano.Ledger.Address

Associated Types

type Rep WithdrawalsTypeType #

Show Withdrawals 
Instance details

Defined in Cardano.Ledger.Address

DecCBOR Withdrawals 
Instance details

Defined in Cardano.Ledger.Address

EncCBOR Withdrawals 
Instance details

Defined in Cardano.Ledger.Address

Methods

encCBORWithdrawalsEncoding Source #

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

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

NFData Withdrawals 
Instance details

Defined in Cardano.Ledger.Address

Methods

rnfWithdrawals → () #

Eq Withdrawals 
Instance details

Defined in Cardano.Ledger.Address

NoThunks Withdrawals 
Instance details

Defined in Cardano.Ledger.Address

type Rep Withdrawals 
Instance details

Defined in Cardano.Ledger.Address

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

class EraTxCert era ⇒ ShelleyEraTxCert era where Source #

pattern MirTxCert ∷ (ShelleyEraTxCert era, ProtVerAtMost era 8) ⇒ MIRCertTxCert era Source #

data MIRCert Source #

Move instantaneous rewards certificate

Constructors

MIRCert 

Fields

Instances

Instances details
ToJSON MIRCert Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Generic MIRCert Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep MIRCertTypeType #

Methods

fromMIRCertRep MIRCert x #

toRep MIRCert x → MIRCert #

Show MIRCert Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

showsPrecIntMIRCertShowS #

showMIRCertString #

showList ∷ [MIRCert] → ShowS #

DecCBOR MIRCert Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

EncCBOR MIRCert Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

encCBORMIRCertEncoding Source #

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

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

NFData MIRCert Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnfMIRCert → () #

Eq MIRCert Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

(==)MIRCertMIRCertBool #

(/=)MIRCertMIRCertBool #

Ord MIRCert Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

compareMIRCertMIRCertOrdering #

(<)MIRCertMIRCertBool #

(<=)MIRCertMIRCertBool #

(>)MIRCertMIRCertBool #

(>=)MIRCertMIRCertBool #

maxMIRCertMIRCertMIRCert #

minMIRCertMIRCertMIRCert #

NoThunks MIRCert Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep MIRCert Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep MIRCert = D1 ('MetaData "MIRCert" "Cardano.Ledger.Shelley.TxCert" "cardano-ledger-shelley-1.16.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)))

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 #

Methods

fromMIRPotRep MIRPot x #

toRep MIRPot x → MIRPot #

Show MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

showsPrecIntMIRPotShowS #

showMIRPotString #

showList ∷ [MIRPot] → ShowS #

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 → () #

Eq MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

(==)MIRPotMIRPotBool #

(/=)MIRPotMIRPotBool #

Ord MIRPot Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

compareMIRPotMIRPotOrdering #

(<)MIRPotMIRPotBool #

(<=)MIRPotMIRPotBool #

(>)MIRPotMIRPotBool #

(>=)MIRPotMIRPotBool #

maxMIRPotMIRPotMIRPot #

minMIRPotMIRPotMIRPot #

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.16.0.0-inplace" 'False) (C1 ('MetaCons "ReservesMIR" 'PrefixI 'False) (U1TypeType) :+: C1 ('MetaCons "TreasuryMIR" 'PrefixI 'False) (U1TypeType))

data MIRTarget 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
ToJSON MIRTarget Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Generic MIRTarget Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Associated Types

type Rep MIRTargetTypeType #

Methods

fromMIRTargetRep MIRTarget x #

toRep MIRTarget x → MIRTarget #

Show MIRTarget Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

showsPrecIntMIRTargetShowS #

showMIRTargetString #

showList ∷ [MIRTarget] → ShowS #

DecCBOR MIRTarget Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

EncCBOR MIRTarget Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

encCBORMIRTargetEncoding Source #

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

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

NFData MIRTarget Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

rnfMIRTarget → () #

Eq MIRTarget Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

Methods

(==)MIRTargetMIRTargetBool #

(/=)MIRTargetMIRTargetBool #

Ord MIRTarget Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

NoThunks MIRTarget Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

type Rep MIRTarget Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

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

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_224Nat Source #

HashAlgorithm Blake2b_256 
Instance details

Defined in Cardano.Crypto.Hash.Blake2b

Associated Types

type SizeHash Blake2b_256Nat Source #

HashAlgorithm Keccak256 
Instance details

Defined in Cardano.Crypto.Hash.Keccak256

Associated Types

type SizeHash Keccak256Nat Source #

HashAlgorithm NeverHash 
Instance details

Defined in Cardano.Crypto.Hash.NeverUsed

Associated Types

type SizeHash NeverHashNat Source #

HashAlgorithm RIPEMD160 
Instance details

Defined in Cardano.Crypto.Hash.RIPEMD160

Associated Types

type SizeHash RIPEMD160Nat Source #

HashAlgorithm SHA256 
Instance details

Defined in Cardano.Crypto.Hash.SHA256

Associated Types

type SizeHash SHA256Nat Source #

HashAlgorithm SHA3_256 
Instance details

Defined in Cardano.Crypto.Hash.SHA3_256

Associated Types

type SizeHash SHA3_256Nat Source #

(KnownNat n, CmpNat n 33 ~ 'LT) ⇒ HashAlgorithm (Blake2bPrefix n) 
Instance details

Defined in Cardano.Crypto.Hash.Short

Associated Types

type SizeHash (Blake2bPrefix n) ∷ Nat Source #

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

fromStringString → Q (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 ⇒ 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) ∷ TypeType #

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

readPrec ∷ ReadPrec (Hash h a) #

readListPrec ∷ ReadPrec [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 #

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

(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, Typeable a) ⇒ EncCBOR (Hash h a) 
Instance details

Defined in Cardano.Ledger.Binary.Encoding.EncCBOR

Methods

encCBORHash h a → Encoding Source #

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

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

HashAlgorithm h ⇒ SafeToHash (Hash h i)

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

Instance details

Defined in Cardano.Ledger.Hashes

NFData (Hash h a) 
Instance details

Defined in Cardano.Crypto.Hash.Class

Methods

rnfHash h a → () #

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 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.0.0-23f62f43b5ff9b1ea2de52a5d5b93b2bcb91ce88174fddbcca6d93648313d72b" 'True) (C1 ('MetaCons "UnsafeHashRep" 'PrefixI 'False) (S1 ('MetaSel ('NothingMaybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (PackedBytes (SizeHash h)))))

txIdTxBodyEraTxBody era ⇒ TxBody era → TxId Source #

txIdTxEraTx era ⇒ Tx era → TxId Source #

bBodySizeEraSegWits era ⇒ ProtVerTxSeq era → Int 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.

hashTxAuxDataEraTxAuxData era ⇒ TxAuxData era → TxAuxDataHash Source #

Compute a hash of TxAuxData

mkCoinTxOutEraTxOut era ⇒ AddrCoinTxOut 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 Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Tx.Internal

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

Instances

Instances details
type Tx ShelleyEra Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Tx.Internal

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

sizeTxFSimpleGetter (Tx era) Integer Source #

For fee calculation and estimations of impact on block space

wireSizeTxFSimpleGetter (Tx era) Word32 Source #

For end use by eg. diffusion layer in transaction submission protocol

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

Defined in Cardano.Ledger.Shelley.TxBody

class (EraTxOut era, EraTxCert era, EraPParams era, HashAnnotated (TxBody era) EraIndependentTxBody, 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) Source #

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

feeTxBodyLLens' (TxBody era) Coin Source #

withdrawalsTxBodyLLens' (TxBody era) Withdrawals Source #

auxDataHashTxBodyLLens' (TxBody era) (StrictMaybe TxAuxDataHash) Source #

spendableInputsTxBodyFSimpleGetter (TxBody 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 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.

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

getTotalDepositsTxBody Source #

Arguments

PParams era 
→ (KeyHash 'StakePoolBool)

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

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

The output of a UTxO for a particular era

Instances

Instances details
type TxOut ShelleyEra Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxOut

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.

type family Value era Source #

A value is something which quantifies a transaction output.

Instances

Instances details
type Value ShelleyEra Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Era

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

Instances

Instances details
type TxAuxData ShelleyEra 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) ⇒ 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

validateTxAuxDataProtVerTxAuxData era → Bool Source #

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

Instances

Instances details
type TxWits ShelleyEra Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxWits

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

Instances

Instances details
type NativeScript ShelleyEra 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 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 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 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

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 ⇒ PoolParamsTxCert era Source #

type family TxCertUpgradeError era Source #

Instances

Instances details
type TxCertUpgradeError ShelleyEra Source # 
Instance details

Defined in Cardano.Ledger.Shelley.TxCert

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

Instances

Instances details
type TxCert ShelleyEra 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), 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

mkRegPoolTxCertPoolParamsTxCert era Source #

getRegPoolTxCertTxCert era → Maybe PoolParams 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.

data PoolCert Source #

Constructors

RegPool !PoolParams

A stake pool registration certificate.

RetirePool !(KeyHash 'StakePool) !EpochNo

A stake pool retirement certificate.

Instances

Instances details
ToJSON PoolCert 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Generic PoolCert 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Associated Types

type Rep PoolCertTypeType #

Methods

fromPoolCertRep PoolCert x #

toRep PoolCert x → PoolCert #

Show PoolCert 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

showsPrecIntPoolCertShowS #

showPoolCertString #

showList ∷ [PoolCert] → ShowS #

EncCBOR PoolCert 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

encCBORPoolCertEncoding Source #

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

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

NFData PoolCert 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

rnfPoolCert → () #

Eq PoolCert 
Instance details

Defined in Cardano.Ledger.Core.TxCert

Methods

(==)PoolCertPoolCertBool #

(/=)PoolCertPoolCertBool #

Ord PoolCert 
Instance details

Defined in Cardano.Ledger.Core.TxCert

NoThunks PoolCert 
Instance details

Defined in Cardano.Ledger.Core.TxCert

type Rep PoolCert 
Instance details

Defined in Cardano.Ledger.Core.TxCert

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

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 #

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 → () #

Eq RewardType 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

(==)RewardTypeRewardTypeBool #

(/=)RewardTypeRewardTypeBool #

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

Defined in Cardano.Ledger.Rewards

Generic Reward 
Instance details

Defined in Cardano.Ledger.Rewards

Associated Types

type Rep RewardTypeType #

Methods

fromRewardRep Reward x #

toRep Reward x → Reward #

Show Reward 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

showsPrecIntRewardShowS #

showRewardString #

showList ∷ [Reward] → ShowS #

DecCBOR Reward 
Instance details

Defined in Cardano.Ledger.Rewards

EncCBOR Reward 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

encCBORRewardEncoding Source #

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

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

NFData Reward 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

rnfReward → () #

Eq Reward 
Instance details

Defined in Cardano.Ledger.Rewards

Methods

(==)RewardRewardBool #

(/=)RewardRewardBool #

Ord Reward

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

Defined in Cardano.Ledger.Rewards

type Rep Reward 
Instance details

Defined in Cardano.Ledger.Rewards

type Rep Reward = D1 ('MetaData "Reward" "Cardano.Ledger.Rewards" "cardano-ledger-core-1.17.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))))

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

Methods

fromPParams era → Rep (PParams era) x #

toRep (PParams era) x → PParams era #

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

Defined in Cardano.Ledger.Core.PParams

Methods

showsPrecIntPParams era → ShowS #

showPParams era → String #

showList ∷ [PParams era] → ShowS #

(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 → () #

Eq (PParamsHKD Identity era) ⇒ Eq (PParams era) 
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) 
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) 
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.17.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 #

Methods

fromPParamsUpdate era → Rep (PParamsUpdate era) x #

toRep (PParamsUpdate era) x → PParamsUpdate era #

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

Defined in Cardano.Ledger.Core.PParams

Methods

showsPrecIntPParamsUpdate era → ShowS #

showPParamsUpdate era → String #

showList ∷ [PParamsUpdate era] → ShowS #

(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 → () #

Eq (PParamsHKD StrictMaybe era) ⇒ Eq (PParamsUpdate era) 
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) 
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) 
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.17.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 Source # 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

type family UpgradePParams (f ∷ TypeType) era Source #

 

Instances

Instances details
type UpgradePParams f ShelleyEra 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 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
EraPParams ShelleyEra Source # 
Instance details

Defined in Cardano.Ledger.Shelley.PParams

Methods

applyPPUpdatesPParams ShelleyEraPParamsUpdate ShelleyEraPParams ShelleyEra Source #

emptyPParamsIdentityPParamsHKD Identity ShelleyEra Source #

emptyPParamsStrictMaybePParamsHKD StrictMaybe ShelleyEra Source #

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

ppDGSimpleGetter (PParams ShelleyEra) UnitInterval Source #

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

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

ppProtocolVersionLLens' (PParams ShelleyEra) ProtVer Source #

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

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

hkdMinPoolCostL ∷ ∀ (f ∷ TypeType). HKDFunctor f ⇒ Lens' (PParamsHKD f ShelleyEra) (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 

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

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

Hash a given public key

type HASH = Blake2b_256 Source #

Hashing algorithm used for hashing everything, except addresses, for which ADDRHASH is used.

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 KeyHash (r ∷ KeyRole) Source #

Discriminated hash of public Key

Constructors

KeyHash 

Instances

Instances details
HasKeyRole KeyHash 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

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

FromJSON (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

FromJSONKey (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSON (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSONKey (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Generic (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Associated Types

type Rep (KeyHash r) ∷ TypeType #

Methods

fromKeyHash r → Rep (KeyHash r) x #

toRep (KeyHash r) x → KeyHash r #

Show (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

showsPrecIntKeyHash r → ShowS #

showKeyHash r → String #

showList ∷ [KeyHash r] → ShowS #

Typeable r ⇒ FromCBOR (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

fromCBORDecoder s (KeyHash r) Source #

labelProxy (KeyHash r) → Text Source #

Typeable r ⇒ ToCBOR (KeyHash r) 
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) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

decCBORDecoder s (KeyHash r) Source #

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

labelProxy (KeyHash r) → Text Source #

Typeable r ⇒ EncCBOR (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

encCBORKeyHash r → Encoding Source #

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

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

Default (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

defKeyHash r Source #

NFData (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

rnfKeyHash r → () #

Eq (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

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

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

Ord (KeyHash r) 
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) 
Instance details

Defined in Cardano.Ledger.Hashes

NoThunks (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

type Rep (KeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

newtype ScriptHash Source #

Instances

Instances details
FromJSON ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

FromJSONKey ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSON ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSONKey ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

Generic ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

Associated Types

type Rep ScriptHashTypeType #

Show ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

FromCBOR ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

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

Defined in Cardano.Ledger.Hashes

EncCBOR ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

encCBORScriptHashEncoding Source #

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

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

NFData ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

rnfScriptHash → () #

Eq ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

(==)ScriptHashScriptHashBool #

(/=)ScriptHashScriptHashBool #

Ord ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

MemPack ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

NoThunks ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

type Rep ScriptHash 
Instance details

Defined in Cardano.Ledger.Hashes

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

newtype VRFVerKeyHash (r ∷ KeyRoleVRF) Source #

Discriminated hash of VRF Verification Key

Instances

Instances details
FromJSON (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

FromJSONKey (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSON (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

ToJSONKey (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Generic (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Associated Types

type Rep (VRFVerKeyHash r) ∷ TypeType #

Methods

fromVRFVerKeyHash r → Rep (VRFVerKeyHash r) x #

toRep (VRFVerKeyHash r) x → VRFVerKeyHash r #

Show (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable r ⇒ FromCBOR (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable r ⇒ ToCBOR (VRFVerKeyHash r) 
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) 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable r ⇒ EncCBOR (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

encCBORVRFVerKeyHash r → Encoding Source #

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

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

Default (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

defVRFVerKeyHash r Source #

NFData (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

rnfVRFVerKeyHash r → () #

Eq (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

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

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

Ord (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

NoThunks (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

type Rep (VRFVerKeyHash r) 
Instance details

Defined in Cardano.Ledger.Hashes

newtype TxAuxDataHash Source #

Instances

Instances details
ToJSON TxAuxDataHash 
Instance details

Defined in Cardano.Ledger.Hashes

Generic TxAuxDataHash 
Instance details

Defined in Cardano.Ledger.Hashes

Associated Types

type Rep TxAuxDataHashTypeType #

Show TxAuxDataHash 
Instance details

Defined in Cardano.Ledger.Hashes

DecCBOR TxAuxDataHash 
Instance details

Defined in Cardano.Ledger.Hashes

EncCBOR TxAuxDataHash 
Instance details

Defined in Cardano.Ledger.Hashes

NFData TxAuxDataHash 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

rnfTxAuxDataHash → () #

Eq TxAuxDataHash 
Instance details

Defined in Cardano.Ledger.Hashes

Ord TxAuxDataHash 
Instance details

Defined in Cardano.Ledger.Hashes

NoThunks TxAuxDataHash 
Instance details

Defined in Cardano.Ledger.Hashes

type Rep TxAuxDataHash 
Instance details

Defined in Cardano.Ledger.Hashes

type Rep TxAuxDataHash = D1 ('MetaData "TxAuxDataHash" "Cardano.Ledger.Hashes" "cardano-ledger-core-1.17.0.0-inplace" 'True) (C1 ('MetaCons "TxAuxDataHash" 'PrefixI 'True) (S1 ('MetaSel ('Just "unTxAuxDataHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SafeHash EraIndependentTxAuxData))))

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

Defined in Cardano.Ledger.Hashes

ToJSON (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

Show (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

showsPrecIntSafeHash i → ShowS #

showSafeHash i → String #

showList ∷ [SafeHash i] → ShowS #

Typeable i ⇒ FromCBOR (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable i ⇒ ToCBOR (SafeHash i) 
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) 
Instance details

Defined in Cardano.Ledger.Hashes

Typeable i ⇒ EncCBOR (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

encCBORSafeHash i → Encoding Source #

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

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

SafeToHash (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

Default (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

defSafeHash i Source #

NFData (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

rnfSafeHash i → () #

Eq (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

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

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

Ord (SafeHash i) 
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 #

HeapWords (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

Methods

heapWordsSafeHash i → Int Source #

MemPack (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

NoThunks (SafeHash i) 
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 
Instance details

Defined in Cardano.Ledger.Hashes

SafeToHash ShortByteString 
Instance details

Defined in Cardano.Ledger.Hashes

SafeToHash AnchorData 
Instance details

Defined in Cardano.Ledger.BaseTypes

SafeToHash PlutusBinary 
Instance details

Defined in Cardano.Ledger.Plutus.Language

SafeToHash (SafeHash i) 
Instance details

Defined in Cardano.Ledger.Hashes

SafeToHash (Plutus l) 
Instance details

Defined in Cardano.Ledger.Plutus.Language

SafeToHash (MultiSig era) Source # 
Instance details

Defined in Cardano.Ledger.Shelley.Scripts

SafeToHash (ShelleyTx era) Source # 
Instance details

Defined in