Safe Haskell | None |
---|---|
Language | Haskell2010 |
Interface to the Shelley ledger for the purposes of managing a Shelley mempool.
Synopsis
-
class
(
ChainData
(
Tx
era),
AnnotatedData
(
Tx
era),
Eq
(
ApplyTxError
era),
Show
(
ApplyTxError
era),
Typeable
(
ApplyTxError
era),
SerialisableData
(
ApplyTxError
era),
STS
(
EraRule
"LEDGER" era),
BaseM
(
EraRule
"LEDGER" era) ~
ShelleyBase
,
Environment
(
EraRule
"LEDGER" era) ~
LedgerEnv
era,
State
(
EraRule
"LEDGER" era) ~
MempoolState
era,
Signal
(
EraRule
"LEDGER" era) ~
Tx
era,
PredicateFailure
(
EraRule
"LEDGER" era) ~
LedgerPredicateFailure
era) =>
ApplyTx
era
where
- applyTx :: MonadError ( ApplyTxError era) m => Globals -> MempoolEnv era -> MempoolState era -> Tx era -> m ( MempoolState era, Validated ( Tx era))
- reapplyTx :: MonadError ( ApplyTxError era) m => Globals -> MempoolEnv era -> MempoolState era -> Validated ( Tx era) -> m ( MempoolState era)
- newtype ApplyTxError era = ApplyTxError [ PredicateFailure ( EraRule "LEDGER" era)]
- data Validated tx
- extractTx :: Validated tx -> tx
- coerceValidated :: Coercible a b => Validated a -> Validated b
- translateValidated :: forall era f. TranslateEra era f => TranslationContext era -> Validated (f ( PreviousEra era)) -> Except ( TranslationError era f) ( Validated (f era))
- type MempoolEnv era = LedgerEnv era
- type MempoolState era = LedgerState era
- applyTxsTransition :: forall era m. ( ApplyTx era, MonadError ( ApplyTxError era) m) => Globals -> MempoolEnv era -> Seq ( Tx era) -> MempoolState era -> m ( MempoolState era)
- unsafeMakeValidated :: tx -> Validated tx
- applyTxs :: ( ApplyTx era, MonadError ( ApplyTxError era) m) => Globals -> SlotNo -> Seq ( Tx era) -> NewEpochState era -> m ( NewEpochState era)
- mkMempoolEnv :: NewEpochState era -> SlotNo -> MempoolEnv era
- mkMempoolState :: NewEpochState era -> MempoolState era
- overNewEpochState :: Functor f => ( MempoolState era -> f ( MempoolState era)) -> NewEpochState era -> f ( NewEpochState era)
Documentation
class ( ChainData ( Tx era), AnnotatedData ( Tx era), Eq ( ApplyTxError era), Show ( ApplyTxError era), Typeable ( ApplyTxError era), SerialisableData ( ApplyTxError era), STS ( EraRule "LEDGER" era), BaseM ( EraRule "LEDGER" era) ~ ShelleyBase , Environment ( EraRule "LEDGER" era) ~ LedgerEnv era, State ( EraRule "LEDGER" era) ~ MempoolState era, Signal ( EraRule "LEDGER" era) ~ Tx era, PredicateFailure ( EraRule "LEDGER" era) ~ LedgerPredicateFailure era) => ApplyTx era where Source #
Nothing
applyTx :: MonadError ( ApplyTxError era) m => Globals -> MempoolEnv era -> MempoolState era -> Tx era -> m ( MempoolState era, Validated ( Tx era)) Source #
Validate a transaction against a mempool state, and return both the new
mempool state and a "validated"
TxInBlock
.
The meaning of being "validated" depends on the era. In general, a
TxInBlock
has had all checks run, and can now only fail due to checks
which depend on the state; most notably, that UTxO inputs disappear.
reapplyTx :: MonadError ( ApplyTxError era) m => Globals -> MempoolEnv era -> MempoolState era -> Validated ( Tx era) -> m ( MempoolState era) Source #
Reapply a previously validated
Tx
.
This applies the (validated) transaction to a new mempool state. It may fail due to the mempool state changing (for example, a needed output having already been spent). It should not fail due to any static check (such as cryptographic checks).
Implementations of this function may optionally skip the performance of any static checks. This is not required, but strongly encouraged since this function will be called each time the mempool revalidates transactions against a new mempool state.
Instances
ShelleyEraCrypto c => ApplyTx ( ShelleyEra c) Source # | |
Defined in Cardano.Ledger.Shelley.API.Mempool applyTx :: MonadError ( ApplyTxError ( ShelleyEra c)) m => Globals -> MempoolEnv ( ShelleyEra c) -> MempoolState ( ShelleyEra c) -> Tx ( ShelleyEra c) -> m ( MempoolState ( ShelleyEra c), Validated ( Tx ( ShelleyEra c))) Source # reapplyTx :: MonadError ( ApplyTxError ( ShelleyEra c)) m => Globals -> MempoolEnv ( ShelleyEra c) -> MempoolState ( ShelleyEra c) -> Validated ( Tx ( ShelleyEra c)) -> m ( MempoolState ( ShelleyEra c)) Source # |
newtype ApplyTxError era Source #
ApplyTxError [ PredicateFailure ( EraRule "LEDGER" era)] |
Instances
Eq ( PredicateFailure ( EraRule "LEDGER" era)) => Eq ( ApplyTxError era) Source # | |
Defined in Cardano.Ledger.Shelley.API.Mempool (==) :: ApplyTxError era -> ApplyTxError era -> Bool Source # (/=) :: ApplyTxError era -> ApplyTxError era -> Bool Source # |
|
Show ( PredicateFailure ( EraRule "LEDGER" era)) => Show ( ApplyTxError era) Source # | |
Defined in Cardano.Ledger.Shelley.API.Mempool |
|
( Era era, ToCBOR ( PredicateFailure ( EraRule "LEDGER" era))) => ToCBOR ( ApplyTxError era) Source # | |
Defined in Cardano.Ledger.Shelley.API.Mempool toCBOR :: ApplyTxError era -> Encoding Source # encodedSizeExpr :: ( forall t. ToCBOR t => Proxy t -> Size ) -> Proxy ( ApplyTxError era) -> Size Source # encodedListSizeExpr :: ( forall t. ToCBOR t => Proxy t -> Size ) -> Proxy [ ApplyTxError era] -> Size Source # |
|
( Era era, FromCBOR ( PredicateFailure ( EraRule "LEDGER" era))) => FromCBOR ( ApplyTxError era) Source # | |
Defined in Cardano.Ledger.Shelley.API.Mempool |
A newtype which indicates that a transaction has been validated against some chain state.
translateValidated :: forall era f. TranslateEra era f => TranslationContext era -> Validated (f ( PreviousEra era)) -> Except ( TranslationError era f) ( Validated (f era)) Source #
Translate a validated transaction across eras.
This is not a
TranslateEra
instance since
Validated
is not itself
era-parametrised.
Exports for testing
type MempoolEnv era = LedgerEnv era Source #
type MempoolState era = LedgerState era Source #
applyTxsTransition :: forall era m. ( ApplyTx era, MonadError ( ApplyTxError era) m) => Globals -> MempoolEnv era -> Seq ( Tx era) -> MempoolState era -> m ( MempoolState era) Source #
unsafeMakeValidated :: tx -> Validated tx Source #
Exports for compatibility
applyTxs :: ( ApplyTx era, MonadError ( ApplyTxError era) m) => Globals -> SlotNo -> Seq ( Tx era) -> NewEpochState era -> m ( NewEpochState era) Source #
Old
applyTxs
mkMempoolEnv :: NewEpochState era -> SlotNo -> MempoolEnv era Source #
Construct the environment used to validate transactions from the full ledger state.
Note that this function also takes a slot. During slot validation, the slot given here is the slot of the block containing the transactions. This slot is used for quite a number of things, but in general these do not determine the validity of the transaction. There are two exceptions:
- Each transaction has a ttl (time-to-live) value. If the slot is beyond this value, then the transaction is invalid.
- If the transaction contains a protocol update proposal, then it may only be included until a certain number of slots before the end of the epoch. A protocol update proposal submitted after this is considered invalid.
mkMempoolState :: NewEpochState era -> MempoolState era Source #
Construct a mempool state from the wider ledger state.
The given mempool state may then be evolved using
applyTxs
, but should be
regenerated when the ledger state gets updated (e.g. through application of
a new block).
overNewEpochState :: Functor f => ( MempoolState era -> f ( MempoolState era)) -> NewEpochState era -> f ( NewEpochState era) Source #
Transform a function over mempool states to one over the full
NewEpochState
.