ouroboros-consensus-0.21.0.0: Consensus layer for the Ouroboros blockchain protocol
Safe HaskellSafe-Inferred
LanguageHaskell2010

Ouroboros.Consensus.Ledger.SupportsMempool

Synopsis

Documentation

type family ApplyTxErr blk ∷ Type Source #

Updating the ledger with a single transaction may result in a different error type as when updating it with a block

Instances

Instances details
type ApplyTxErr (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type ApplyTxErr (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype ByteSize32 Source #

We intentionally do not declare a Num instance! We prefer ByteSize32 to occur explicitly in the code where possible, for legibility/perspicuousness. We also do not need nor want subtraction.

This data type measures the size of a transaction, the sum of the sizes of txs in a block, the sum of the sizes of the txs in the mempool, etc. None of those will ever need to represent gigabytes, so 32 bits suffice. But 16 bits would not.

This is modular arithmetic, so uses need to be concerned with overflow. For example, see the related guard in pureTryAddTx. One important element is anticipating the possibility of very large summands injected by the adversary.

There is a temptation to use Natural here, since it can never overflow. However, some points in the interface do not easily handle Naturals, such as encoders. Thus Natural would merely defer the overflow concern, and even risks instilling a false sense that overflow need not be considered at all.

Constructors

ByteSize32 

Fields

Instances

Instances details
Monoid ByteSize32 Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

Semigroup ByteSize32 Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

Show ByteSize32 Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

NFData ByteSize32 Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

Methods

rnfByteSize32 → () #

Eq ByteSize32 Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

Methods

(==)ByteSize32ByteSize32Bool #

(/=)ByteSize32ByteSize32Bool #

Ord ByteSize32 Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

NoThunks ByteSize32 Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

HasByteSize ByteSize32 Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

Serialise ByteSize32 Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

Measure (IgnoringOverflow ByteSize32) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

class HasTxId tx ⇒ ConvertRawTxId tx where Source #

Extract the raw hash bytes from a TxId.

Methods

toRawTxIdHashTxId tx → ShortByteString Source #

NOTE: The composition toRawTxIdHash . txId must satisfy the same properties as defined in the docs of txId.

data family GenTx blk ∷ Type Source #

Generalized transaction

The mempool (and, accordingly, blocks) consist of "generalized transactions"; this could be "proper" transactions (transferring funds) but also other kinds of things such as update proposals, delegations, etc.

Instances

Instances details
Inject GenTx Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Nary

Methods

inject ∷ ∀ x (xs ∷ [Type]). CanHardFork xs ⇒ Exactly xs BoundIndex xs x → GenTx x → GenTx (HardForkBlock xs) Source #

Isomorphic GenTx Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Embed.Unary

Methods

projectNoHardForks blk ⇒ GenTx (HardForkBlock '[blk]) → GenTx blk Source #

injectNoHardForks blk ⇒ GenTx blk → GenTx (HardForkBlock '[blk]) Source #

Typeable xs ⇒ ShowProxy (GenTx (HardForkBlock xs) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

(Typeable m, Typeable a) ⇒ ShowProxy (GenTx (DualBlock m a) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (GenTx (DualBlock m a)) → String Source #

Typeable xs ⇒ ShowProxy (TxId (GenTx (HardForkBlock xs)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

(Typeable m, Typeable a) ⇒ ShowProxy (TxId (GenTx (DualBlock m a)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (TxId (GenTx (DualBlock m a))) → String Source #

Generic (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (Validated (GenTx (HardForkBlock xs))) ∷ TypeType #

Generic (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (GenTx (HardForkBlock xs)) ∷ TypeType #

Methods

fromGenTx (HardForkBlock xs) → Rep (GenTx (HardForkBlock xs)) x #

toRep (GenTx (HardForkBlock xs)) x → GenTx (HardForkBlock xs) #

Generic (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (TxId (GenTx (HardForkBlock xs))) ∷ TypeType #

Methods

fromTxId (GenTx (HardForkBlock xs)) → Rep (TxId (GenTx (HardForkBlock xs))) x #

toRep (TxId (GenTx (HardForkBlock xs))) x → TxId (GenTx (HardForkBlock xs)) #

CanHardFork xs ⇒ Show (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Bridge m a ⇒ Show (Validated (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntValidated (GenTx (DualBlock m a)) → ShowS #

showValidated (GenTx (DualBlock m a)) → String #

showList ∷ [Validated (GenTx (DualBlock m a))] → ShowS #

CanHardFork xs ⇒ Show (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

showsPrecIntGenTx (HardForkBlock xs) → ShowS #

showGenTx (HardForkBlock xs) → String #

showList ∷ [GenTx (HardForkBlock xs)] → ShowS #

Bridge m a ⇒ Show (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntGenTx (DualBlock m a) → ShowS #

showGenTx (DualBlock m a) → String #

showList ∷ [GenTx (DualBlock m a)] → ShowS #

CanHardFork xs ⇒ Show (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

showsPrecIntTxId (GenTx (HardForkBlock xs)) → ShowS #

showTxId (GenTx (HardForkBlock xs)) → String #

showList ∷ [TxId (GenTx (HardForkBlock xs))] → ShowS #

Show (GenTxId m) ⇒ Show (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntTxId (GenTx (DualBlock m a)) → ShowS #

showTxId (GenTx (DualBlock m a)) → String #

showList ∷ [TxId (GenTx (DualBlock m a))] → ShowS #

CanHardFork xs ⇒ Eq (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ Eq (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

(==)GenTx (HardForkBlock xs) → GenTx (HardForkBlock xs) → Bool #

(/=)GenTx (HardForkBlock xs) → GenTx (HardForkBlock xs) → Bool #

CanHardFork xs ⇒ Eq (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

(==)TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool #

(/=)TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool #

Eq (GenTxId m) ⇒ Eq (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

(==)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(/=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

CanHardFork xs ⇒ Ord (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Ord (GenTxId m) ⇒ Ord (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

compareTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Ordering #

(<)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(<=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(>)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(>=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

maxTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) #

minTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) #

CanHardFork xs ⇒ NoThunks (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

NoThunks (Validated (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ NoThunks (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

NoThunks (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ NoThunks (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

NoThunks (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

CanHardFork xs ⇒ HasTxId (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

txIdGenTx (HardForkBlock xs) → TxId (GenTx (HardForkBlock xs)) Source #

Bridge m a ⇒ HasTxId (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

txIdGenTx (DualBlock m a) → TxId (GenTx (DualBlock m a)) Source #

All CondenseConstraints xs ⇒ Condense (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

All CondenseConstraints xs ⇒ Condense (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

type Rep (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.21.0.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
type Rep (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (GenTx (HardForkBlock xs)) = D1 ('MetaData "GenTx" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.21.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTx xs))))
type Rep (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.21.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
newtype Validated (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

data Validated (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

newtype GenTx (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data GenTx (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type GenTxId blk = TxId (GenTx blk) Source #

Shorthand: ID of a generalized transaction

class HasByteSize a where Source #

Methods

txMeasureByteSize ∷ a → ByteSize32 Source #

The byte size component (of TxMeasure)

class (Show (TxId tx), Ord (TxId tx), NoThunks (TxId tx)) ⇒ HasTxId tx where Source #

Transactions with an identifier

The mempool will use these to locate transactions, so two different transactions should have different identifiers.

Methods

txId ∷ tx → TxId tx Source #

Return the TxId of a GenTx.

NOTE: a TxId must be unique up to ledger rules, i.e., two GenTxs with the same TxId must be the same transaction according to the ledger. However, we do not assume that a TxId uniquely determines a GenTx: two GenTxs with the same TxId can differ in, e.g., witnesses.

Should be cheap as this will be called often.

Instances

Instances details
CanHardFork xs ⇒ HasTxId (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

txIdGenTx (HardForkBlock xs) → TxId (GenTx (HardForkBlock xs)) Source #

Bridge m a ⇒ HasTxId (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

txIdGenTx (DualBlock m a) → TxId (GenTx (DualBlock m a)) Source #

class HasTxs blk where Source #

Collect all transactions from a block

This is used for tooling only. We don't require it as part of RunNode (and cannot, because we cannot give an instance for the dual ledger).

Methods

extractTxs ∷ blk → [GenTx blk] Source #

Return the transactions part of the given block in no particular order.

Instances

Instances details
All HasTxs xs ⇒ HasTxs (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype IgnoringOverflow a Source #

IgnoringOverflow a has the same semantics as a, except it ignores the fact that a can overflow.

For example, Measure Word32 is not lawful, because overflow violates the lattice-ordered monoid law. But Measure (IgnoringOverflow Word32) is lawful, since it explicitly ignores that case.

WARNING: anywhere this type occurs is a very strong indicator that overflow will break assumptions, so overflow must therefore be guarded against.

TODO upstream this to the measure package

Constructors

IgnoringOverflow 

Fields

Instances

Instances details
Monoid a ⇒ Monoid (IgnoringOverflow a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

Semigroup a ⇒ Semigroup (IgnoringOverflow a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

Show a ⇒ Show (IgnoringOverflow a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

NFData a ⇒ NFData (IgnoringOverflow a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

Methods

rnfIgnoringOverflow a → () #

Eq a ⇒ Eq (IgnoringOverflow a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

Ord a ⇒ Ord (IgnoringOverflow a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

Measure (IgnoringOverflow ByteSize32) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

NoThunks a ⇒ NoThunks (IgnoringOverflow a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

HasByteSize a ⇒ HasByteSize (IgnoringOverflow a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.SupportsMempool

class (UpdateLedger blk, TxLimits blk, NoThunks (GenTx blk), NoThunks (Validated (GenTx blk)), NoThunks (Ticked (LedgerState blk)), Show (GenTx blk), Show (Validated (GenTx blk)), Show (ApplyTxErr blk)) ⇒ LedgerSupportsMempool blk where Source #

Minimal complete definition

applyTx, reapplyTx, txForgetValidated

Methods

txInvariantGenTx blk → Bool Source #

Check whether the internal invariants of the transaction hold.

applyTx Source #

Arguments

LedgerConfig blk 
WhetherToIntervene 
SlotNo

Slot number of the block containing the tx

GenTx blk 
TickedLedgerState blk 
Except (ApplyTxErr blk) (TickedLedgerState blk, Validated (GenTx blk)) 

Apply an unvalidated transaction

The mempool expects that the ledger checks the sanity of the transaction' size. The mempool implementation will add any valid transaction as long as there is at least one byte free in the mempool.

reapplyTx Source #

Arguments

HasCallStack 
LedgerConfig blk 
SlotNo

Slot number of the block containing the tx

Validated (GenTx blk) 
TickedLedgerState blk 
Except (ApplyTxErr blk) (TickedLedgerState blk) 

Apply a previously validated transaction to a potentially different ledger state

When we re-apply a transaction to a potentially different ledger state expensive checks such as cryptographic hashes can be skipped, but other checks (such as checking for double spending) must still be done.

txForgetValidatedValidated (GenTx blk) → GenTx blk Source #

Discard the evidence that transaction has been previously validated

Instances

Instances details
CanHardFork xs ⇒ LedgerSupportsMempool (HardForkBlock xs) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Bridge m a ⇒ LedgerSupportsMempool (DualBlock m a) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data family TxId tx ∷ Type Source #

A generalized transaction, GenTx, identifier.

Instances

Instances details
Typeable xs ⇒ ShowProxy (TxId (GenTx (HardForkBlock xs)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

(Typeable m, Typeable a) ⇒ ShowProxy (TxId (GenTx (DualBlock m a)) ∷ Type) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showProxyProxy (TxId (GenTx (DualBlock m a))) → String Source #

Generic (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (TxId (GenTx (HardForkBlock xs))) ∷ TypeType #

Methods

fromTxId (GenTx (HardForkBlock xs)) → Rep (TxId (GenTx (HardForkBlock xs))) x #

toRep (TxId (GenTx (HardForkBlock xs))) x → TxId (GenTx (HardForkBlock xs)) #

CanHardFork xs ⇒ Show (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

showsPrecIntTxId (GenTx (HardForkBlock xs)) → ShowS #

showTxId (GenTx (HardForkBlock xs)) → String #

showList ∷ [TxId (GenTx (HardForkBlock xs))] → ShowS #

Show (GenTxId m) ⇒ Show (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntTxId (GenTx (DualBlock m a)) → ShowS #

showTxId (GenTx (DualBlock m a)) → String #

showList ∷ [TxId (GenTx (DualBlock m a))] → ShowS #

CanHardFork xs ⇒ Eq (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Methods

(==)TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool #

(/=)TxId (GenTx (HardForkBlock xs)) → TxId (GenTx (HardForkBlock xs)) → Bool #

Eq (GenTxId m) ⇒ Eq (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

(==)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(/=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

CanHardFork xs ⇒ Ord (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Ord (GenTxId m) ⇒ Ord (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

compareTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Ordering #

(<)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(<=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(>)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

(>=)TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → Bool #

maxTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) #

minTxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) → TxId (GenTx (DualBlock m a)) #

CanHardFork xs ⇒ NoThunks (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

NoThunks (TxId (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

All CondenseConstraints xs ⇒ Condense (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Condense

SerialiseHFC xs ⇒ SerialiseNodeToClient (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToClient

SerialiseHFC xs ⇒ SerialiseNodeToNode (HardForkBlock xs) (GenTxId (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Serialisation.SerialiseNodeToNode

type Rep (TxId (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (TxId (GenTx (HardForkBlock xs))) = D1 ('MetaData "TxId" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.21.0.0-inplace" 'True) (C1 ('MetaCons "HardForkGenTxId" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkGenTxId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraGenTxId xs))))
newtype TxId (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

newtype TxId (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

class (Measure (TxMeasure blk), HasByteSize (TxMeasure blk), NoThunks (TxMeasure blk), Show (TxMeasure blk)) ⇒ TxLimits blk where Source #

Each block has its limits of how many transactions it can hold. That limit is compared against the sum of measurements taken of each of the transactions in that block.

How we measure the transaction depends of the era that this transaction belongs to (more specifically it depends on the block type to which this transaction will be added). For initial eras (like Byron and initial generations of Shelley based eras) this measure was simply a byte size (block could not be bigger then given size - in bytes - specified by the ledger state). In subsequent eras (starting with Alonzo) this measure was a bit more complex as it had to take other factors into account (like execution units). For details please see the individual instances for the TxLimits.

Associated Types

type TxMeasure blk Source #

The (possibly multi-dimensional) size of a transaction in a block.

Methods

txMeasure Source #

Arguments

LedgerConfig blk

used at least by HFC's composition logic

TickedLedgerState blk 
GenTx blk 
Except (ApplyTxErr blk) (TxMeasure blk) 

The various sizes (bytes, Plutus script ExUnits, etc) of a tx /when it's in a block/

This size is used to compute how many transaction we can put in a block when forging one.

The byte size component in particular might differ from the size of the serialisation used to send and receive the transaction across the network. For example, CBOR-in-CBOR could be used when sending the transaction across the network, requiring a few extra bytes compared to the actual in-block serialisation. Another example is the transaction of the hard-fork combinator which will include an envelope indicating its era when sent across the network. However, when embedded in the respective era's block, there is no need for such envelope. An example from upstream is that the Cardano ledger's "Segregated Witness" encoding scheme contributes to the encoding overhead.

INVARIANT Assuming no hash collisions, the size should be the same in any state in which the transaction is valid. For example, it's acceptable to simply omit the size of ref scripts that could not be found, since their absence implies the tx is invalid. In fact, that invalidity could be reported by this function, but it need not be.

INVARIANT Right x = txMeasure cfg st tx implies @x <= 'blockCapacityTxMeasure cfg st'. Otherwise, the mempool could block forever.

Returns an exception if and only if the transaction violates the per-tx limits.

blockCapacityTxMeasure Source #

Arguments

LedgerConfig blk

at least for symmetry with txMeasure

TickedLedgerState blk 
TxMeasure blk 

What is the allowed capacity for the txs in an individual block?

data family Validated x ∷ Type Source #

" Validated " transaction or block

The ledger defines how to validate transactions and blocks. It's possible the type before and after validation may be distinct (eg Alonzo transactions), which originally motivated this family.

We also gain the related benefit that certain interface functions, such as those that reapply blocks, can have a more precise type now. TODO

Similarly, the Node-to-Client mini protocols can explicitly indicate that the client trusts the blocks from the local server, by having the server send Validated blocks to the client. TODO

Note that validation has different implications for a transaction than for a block. In particular, a validated transaction can be " reapplied " to different ledger states, whereas a validated block must only be " reapplied " to the exact same ledger state (eg as part of rebuilding from an on-disk ledger snapshot).

Since the ledger defines validation, see the ledger details for concrete examples of what determines the validity (wrt to a LedgerState) of a transaction and/or block. Example properties include: a transaction's claimed inputs exist and are still unspent, a block carries a sufficient cryptographic signature, etc.

Instances

Instances details
Generic (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Associated Types

type Rep (Validated (GenTx (HardForkBlock xs))) ∷ TypeType #

CanHardFork xs ⇒ Show (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

Bridge m a ⇒ Show (Validated (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

Methods

showsPrecIntValidated (GenTx (DualBlock m a)) → ShowS #

showValidated (GenTx (DualBlock m a)) → String #

showList ∷ [Validated (GenTx (DualBlock m a))] → ShowS #

CanHardFork xs ⇒ Eq (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

CanHardFork xs ⇒ NoThunks (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

NoThunks (Validated (GenTx (DualBlock m a))) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

type Rep (Validated (GenTx (HardForkBlock xs))) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

type Rep (Validated (GenTx (HardForkBlock xs))) = D1 ('MetaData "Validated" "Ouroboros.Consensus.HardFork.Combinator.Mempool" "ouroboros-consensus-0.21.0.0-inplace" 'True) (C1 ('MetaCons "HardForkValidatedGenTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "getHardForkValidatedGenTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (OneEraValidatedGenTx xs))))
newtype Validated (GenTx (HardForkBlock xs)) Source # 
Instance details

Defined in Ouroboros.Consensus.HardFork.Combinator.Mempool

data Validated (GenTx (DualBlock m a)) Source # 
Instance details

Defined in Ouroboros.Consensus.Ledger.Dual

data WhetherToIntervene Source #

A flag indicating whether the mempool should reject a valid-but-problematic transaction, in order to to protect its author from penalties etc

The primary example is that, as of the Alonzo ledger, a valid transaction can carry an invalid script. If a remote peer sends us such a transaction (over a Node-to-Node protocol), we include it in a block so that the ledger will penalize them them for the invalid script: they wasted our resources by forcing us to run the script to determine it's invalid. But if our local wallet -- which we trust by assumption -- sends us such a transaction (over a Node-to-Client protocol), we would be a good neighbor by rejecting that transaction: they must have made some sort of mistake, and we don't want the ledger to penalize them.

Constructors

DoNotIntervene

We do not trust remote peers, so if a problematic-yet-valid transaction arrives over NTN, we accept it; it will end up in a block and the ledger will penalize them for it.

Intervene

We trust local clients, so if a problematic-yet-valid transaction arrives over NTC, we reject it in order to avoid the ledger penalizing them for it.