cardano-ledger-api-1.7.0.1: Public API for the cardano ledger codebase
Safe HaskellSafe-Inferred
LanguageHaskell2010

Cardano.Ledger.Api.Tx

Description

Transaction building and inspecting relies heavily on lenses (microlens). Therefore, some familiarity with those is necessary. However, you can probably go a long way by simply looking at the examples and try to go from there.

Let's start by defining the GHC extensions and imports.

>>> :set -XScopedTypeVariables
>>> import Test.QuickCheck
>>> import qualified Data.Sequence.Strict as StrictSeq
>>> import Cardano.Ledger.Api.Era (Babbage)
>>> import Lens.Micro
>>> import Test.Cardano.Ledger.Babbage.Arbitrary ()

Here's an example on how to build a Babbage era unbalanced transaction containing a single transaction output using the provided interface.

>>> :{
quickCheck $ \(txOut :: TxOut Babbage) ->
    let
        -- Defining a Babbage era transaction body with a single random transaction output
        txBody = mkBasicTxBody
               & outputsTxBodyL <>~ StrictSeq.singleton txOut
        -- Defining a basic transaction with our transaction body
        tx = mkBasicTx txBody
     in
        -- We verify that the transaction's outputs contains our single random output
        tx ^. bodyTxL . outputsTxBodyL == StrictSeq.singleton txOut
:}
+++ OK, passed 100 tests.
Synopsis

Documentation

Building and inspecting transaction bodies

Shelley onwards

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), ToExpr (Tx era)) => EraTx era #

Minimal complete definition

mkBasicTx, bodyTxL, witsTxL, auxDataTxL, sizeTxF, validateNativeScript, getMinFeeTx, upgradeTx

Associated Types

type Tx era = (r :: Type) | r -> era #

mkBasicTx :: EraTx era => TxBody era -> Tx era #

bodyTxL :: EraTx era => Lens' (Tx era) (TxBody era) #

witsTxL :: EraTx era => Lens' (Tx era) (TxWits era) #

auxDataTxL :: EraTx era => Lens' (Tx era) (StrictMaybe (AuxiliaryData era)) #

sizeTxF :: EraTx era => SimpleGetter (Tx era) Integer #

getMinFeeTx :: EraTx era => PParams era -> Tx era -> Coin #

setMinFeeTx :: EraTx era => PParams era -> Tx era -> Tx era #

Alonzo onwards

class (EraTx era, AlonzoEraTxBody era, AlonzoEraTxWits era) => AlonzoEraTx era #

Minimal complete definition

isValidTxL

Instances

Instances details
Crypto c => AlonzoEraTx (AlonzoEra c) 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Methods

isValidTxL :: Lens' (Tx (AlonzoEra c)) IsValid #

isValidTxL :: AlonzoEraTx era => Lens' (Tx era) IsValid #

newtype IsValid #

Constructors

IsValid Bool 

Instances

Instances details
Generic IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Associated Types

type Rep IsValid :: Type -> Type Source #

Show IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

ToCBOR IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Methods

toCBOR :: IsValid -> Encoding

encodedSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy IsValid -> Size

encodedListSizeExpr :: (forall t. ToCBOR t => Proxy t -> Size) -> Proxy [IsValid] -> Size

DecCBOR IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Methods

decCBOR :: Decoder s IsValid

dropCBOR :: Proxy IsValid -> Decoder s ()

label :: Proxy IsValid -> Text

EncCBOR IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Methods

encCBOR :: IsValid -> Encoding

encodedSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy IsValid -> Size

encodedListSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy [IsValid] -> Size

NFData IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Methods

rnf :: IsValid -> () Source #

Eq IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

NoThunks IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Methods

noThunks :: Context -> IsValid -> IO (Maybe ThunkInfo)

wNoThunks :: Context -> IsValid -> IO (Maybe ThunkInfo)

showTypeOf :: Proxy IsValid -> String

ToExpr IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

Methods

toExpr :: IsValid -> Expr

listToExpr :: [IsValid] -> Expr

type Rep IsValid 
Instance details

Defined in Cardano.Ledger.Alonzo.Tx

type Rep IsValid = D1 ('MetaData "IsValid" "Cardano.Ledger.Alonzo.Tx" "cardano-ledger-alonzo-1.5.1.0-1MT8TTvKeeyGoJw1KVxcth" 'True) (C1 ('MetaCons "IsValid" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

Execution units

evalTxExUnits Source #

Arguments

:: forall era. (AlonzoEraTx era, ExtendedUTxO era, EraUTxO era, ScriptsNeeded era ~ AlonzoScriptsNeeded era, Script era ~ AlonzoScript era, EraPlutusContext 'PlutusV1 era) 
=> PParams era 
-> Tx era

The transaction.

-> UTxO era

The current UTxO set (or the relevant portion for the transaction).

-> EpochInfo (Either Text)

The epoch info, used to translate slots to POSIX time for plutus.

-> SystemStart

The start time of the given block chain.

-> Either (TranslationError (EraCrypto era)) (RedeemerReport era)

We return a map from redeemer pointers to either a failure or a sufficient execution budget. Otherwise, we return a TranslationError manifesting from failed attempts to construct a valid execution context for the given transaction.

Evaluate the execution budgets needed for all the redeemers in a given transaction. If a redeemer is invalid, a failure is returned instead.

The execution budgets in the supplied transaction are completely ignored. The results of evalTxExUnitsWithLogs are intended to replace them.

evaluateTransactionExecutionUnits Source #

Arguments

:: forall era. (AlonzoEraTx era, ExtendedUTxO era, EraUTxO era, ScriptsNeeded era ~ AlonzoScriptsNeeded era, Script era ~ AlonzoScript era, EraPlutusContext 'PlutusV1 era) 
=> PParams era 
-> Tx era

The transaction.

-> UTxO era

The current UTxO set (or the relevant portion for the transaction).

-> EpochInfo (Either Text)

The epoch info, used to translate slots to POSIX time for plutus.

-> SystemStart

The start time of the given block chain.

-> Array Language CostModel

The array of cost models, indexed by the supported languages.

-> Either (TranslationError (EraCrypto era)) (RedeemerReport era)

We return a map from redeemer pointers to either a failure or a sufficient execution budget. Otherwise, we return a TranslationError manifesting from failed attempts to construct a valid execution context for the given transaction.

Deprecated: In favor of evalTxExUnits

Evaluate the execution budgets needed for all the redeemers in a given transaction. If a redeemer is invalid, a failure is returned instead.

The execution budgets in the supplied transaction are completely ignored. The results of evaluateTransactionExecutionUnits are intended to replace them.

evalTxExUnitsWithLogs Source #

Arguments

:: forall era. (AlonzoEraTx era, ExtendedUTxO era, EraUTxO era, ScriptsNeeded era ~ AlonzoScriptsNeeded era, Script era ~ AlonzoScript era, EraPlutusContext 'PlutusV1 era) 
=> PParams era 
-> Tx era

The transaction.

-> UTxO era

The current UTxO set (or the relevant portion for the transaction).

-> EpochInfo (Either Text)

The epoch info, used to translate slots to POSIX time for plutus.

-> SystemStart

The start time of the given block chain.

-> Either (TranslationError (EraCrypto era)) (RedeemerReportWithLogs era)

We return a map from redeemer pointers to either a failure or a sufficient execution budget with logs of the script. Otherwise, we return a TranslationError manifesting from failed attempts to construct a valid execution context for the given transaction.

Unlike evalTxExUnits, this function also returns evaluation logs, useful for debugging.

Evaluate the execution budgets needed for all the redeemers in a given transaction. If a redeemer is invalid, a failure is returned instead.

The execution budgets in the supplied transaction are completely ignored. The results of evaluateTransactionExecutionUnitsWithLogs are intended to replace them.

evaluateTransactionExecutionUnitsWithLogs Source #

Arguments

:: forall era. (AlonzoEraTx era, ExtendedUTxO era, EraUTxO era, ScriptsNeeded era ~ AlonzoScriptsNeeded era, Script era ~ AlonzoScript era, EraPlutusContext 'PlutusV1 era) 
=> PParams era 
-> Tx era

The transaction.

-> UTxO era

The current UTxO set (or the relevant portion for the transaction).

-> EpochInfo (Either Text)

The epoch info, used to translate slots to POSIX time for plutus.

-> SystemStart

The start time of the given block chain.

-> Array Language CostModel

The array of cost models, indexed by the supported languages.

-> Either (TranslationError (EraCrypto era)) (RedeemerReportWithLogs era)

We return a map from redeemer pointers to either a failure or a sufficient execution budget with logs of the script. Otherwise, we return a TranslationError manifesting from failed attempts to construct a valid execution context for the given transaction.

Deprecated: In favor of evalTxExUnitsWithLogs

Evaluate the execution budgets needed for all the redeemers in a given transaction. If a redeemer is invalid, a failure is returned instead.

The execution budgets in the supplied transaction are completely ignored. The results of evaluateTransactionExecutionUnitsWithLogs are intended to replace them.

type RedeemerReportWithLogs era = Map RdmrPtr (Either (TransactionScriptFailure era) ([Text], ExUnits)) Source #

data TransactionScriptFailure era Source #

Script failures that can be returned by evaluateTransactionExecutionUnits.

Constructors

RedeemerNotNeeded !RdmrPtr !(ScriptHash (EraCrypto era))

A redeemer was supplied that does not point to a valid plutus evaluation site in the given transaction.

RedeemerPointsToUnknownScriptHash !RdmrPtr

A redeemer was supplied which points to a script hash which we cannot connect to a Plutus script.

MissingScript !RdmrPtr !(Map RdmrPtr (ScriptPurpose era, Maybe Plutus, ScriptHash (EraCrypto era)))

Missing redeemer. The first parameter is the redeemer pointer which cannot be resolved, and the second parameter is the map of pointers which can be resolved.

MissingDatum !(DataHash (EraCrypto era))

Missing datum.

ValidationFailure ValidationFailed

Plutus evaluation error, for any version

UnknownTxIn !(TxIn (EraCrypto era))

A redeemer points to a transaction input which is not present in the current UTxO.

InvalidTxIn !(TxIn (EraCrypto era))

A redeemer points to a transaction input which is not plutus locked.

IncompatibleBudget !ExBudget

The execution budget that was calculated by the Plutus evaluator is out of bounds.

NoCostModelInLedgerState !Language

There was no cost model for a given version of Plutus in the ledger state

data ValidationFailed where Source #

Constructors

ValidationFailedV1 :: !EvaluationError -> ![Text] -> PlutusDebugLang 'PlutusV1 -> ValidationFailed 
ValidationFailedV2 :: !EvaluationError -> ![Text] -> PlutusDebugLang 'PlutusV2 -> ValidationFailed 
ValidationFailedV3 :: !EvaluationError -> ![Text] -> PlutusDebugLang 'PlutusV3 -> ValidationFailed