Plutus.V2.Ledger.Contexts

  • 1. πŸ“œ Overview

  • 2. πŸ”§ LANGUAGE PRAGMAS & IMPORTS

  • 3. πŸ—„οΈ Data Structures

    • 3.1 πŸͺ TxInInfo

    • 3.2 πŸ“„ TxInfo

    • 3.3 πŸ–‹οΈ ScriptContext

    • 3.4 🎯 ScriptPurpose

  • 4. βš™οΈ Core Functions

    • 4.1 πŸ”Ž findOwnInput

    • 4.2 πŸ“‘ findDatum / findDatumHash

    • 4.3 πŸ”— findTxInByTxOutRef

    • 4.4 πŸ”„ findContinuingOutputs / getContinuingOutputs

    • 4.5 βœ… txSignedBy

    • 4.6 πŸ” ownHashes / ownHash

    • 4.7 πŸ” scriptOutputsAt

    • 4.8 πŸ’° valueLockedBy / valuePaidTo

    • 4.9 πŸ’Έ valueSpent / valueProduced

    • 4.10 🏷️ spendsOutput

  • 5. 🀝 Typeclass Instances

  • 6. 🏭 On-Chain Derivations

  • 7. πŸ“š Glossary


1 πŸ“œ Overview

The Plutus.V2.Ledger.Contexts module defines the on-chain view of pending transactions for Plutus V2 scripts. It provides:

  • Data structures: TxInInfo, TxInfo, and ScriptContext capturing inputs, outputs, redeemers, and transaction metadata.

  • ScriptPurpose: tags indicating why a script is run (e.g. spending, minting).

  • Functions: to locate the current input, retrieve datums, compute continuing outputs, and summarize values.

  • Instances: on-chain equality, Pretty, and serialization via makeIsDataIndexed and makeLift.


2 πŸ”§ LANGUAGE PRAGMAS & IMPORTS

{-# LANGUAGE DataKinds             #-}
{-# LANGUAGE DeriveAnyClass        #-}
{-# LANGUAGE DeriveFunctor         #-}
{-# LANGUAGE DeriveGeneric         #-}
{-# LANGUAGE DerivingVia           #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE NamedFieldPuns        #-}
{-# LANGUAGE NoImplicitPrelude     #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TemplateHaskell       #-}
{-# LANGUAGE TypeApplications      #-}
{-# LANGUAGE UndecidableInstances  #-}
{-# LANGUAGE ViewPatterns          #-}
{-# OPTIONS_GHC -Wno-simplifiable-class-constraints #-}
{-# OPTIONS_GHC -fno-strictness                   #-}
{-# OPTIONS_GHC -fno-specialise                   #-}
{-# OPTIONS_GHC -fno-omit-interface-pragmas       #-}

import GHC.Generics           (Generic)
import PlutusTx               (makeLift, makeIsDataIndexed)
import PlutusTx.AssocMap      (Map)
import PlutusTx.Prelude       hiding (toList)
import Prettyprinter          (Pretty(pretty), nest, vsep, (<+>))

import Plutus.V1.Ledger.Address     (Address(..))
import Plutus.V1.Ledger.Contexts    (ScriptPurpose(..), fromSymbol, pubKeyOutput)
import Plutus.V1.Ledger.Credential  (Credential(..), StakingCredential)
import Plutus.V1.Ledger.Crypto      (PubKeyHash(..))
import Plutus.V1.Ledger.DCert       (DCert(..))
import Plutus.V1.Ledger.Scripts     (ValidatorHash)
import Plutus.V1.Ledger.Time        (POSIXTimeRange)
import Plutus.V1.Ledger.Value       (CurrencySymbol, Value)
import Plutus.V2.Ledger.Tx          (OutputDatum(..), TxId(..), TxOut(..), TxOutRef(..))

import Prelude qualified as Haskell
  • NoImplicitPrelude: uses PlutusTx.Prelude on-chain.

  • DerivingVia and TemplateHaskell for instances.

  • Imports core V1 modules for reuse of types and functions.


3 πŸ—„οΈ Data Structures

3.1 πŸͺ TxInInfo

data TxInInfo = TxInInfo
  { txInInfoOutRef   :: TxOutRef  -- ^ reference to the consumed output
  , txInInfoResolved :: TxOut     -- ^ full output being spent
  } deriving (Generic, Haskell.Show, Haskell.Eq)
  • Usage: Each input pairs a pointer with the resolved TxOut data.

3.2 πŸ“„ TxInfo

data TxInfo = TxInfo
  { txInfoInputs          :: [TxInInfo]            -- ^ inputs being spent
  , txInfoReferenceInputs :: [TxInInfo]            -- ^ reference-only inputs
  , txInfoOutputs         :: [TxOut]               -- ^ outputs produced
  , txInfoFee             :: Value                 -- ^ transaction fee
  , txInfoMint            :: Value                 -- ^ minted value
  , txInfoDCert           :: [DCert]               -- ^ certificates
  , txInfoWdrl            :: Map StakingCredential Integer -- ^ withdrawals
  , txInfoValidRange      :: POSIXTimeRange        -- ^ valid time window
  , txInfoSignatories     :: [PubKeyHash]          -- ^ signing keys
  , txInfoRedeemers       :: Map ScriptPurpose Redeemer  -- ^ redeemer data
  , txInfoData            :: Map DatumHash Datum   -- ^ attached datums
  , txInfoId              :: TxId                  -- ^ transaction hash
  } deriving (Generic, Haskell.Show, Haskell.Eq)
  • Enhancements in V2: adds txInfoReferenceInputs and txInfoRedeemers fields.

3.3 πŸ–‹οΈ ScriptContext

data ScriptContext = ScriptContext
  { scriptContextTxInfo   :: TxInfo
  , scriptContextPurpose  :: ScriptPurpose
  } deriving (Generic, Haskell.Show, Haskell.Eq)
  • Encapsulates the entire transaction view plus why the script runs.

3.4 🎯 ScriptPurpose

Imported from V1:

data ScriptPurpose = Minting CurrencySymbol
                   | Spending TxOutRef
                   | Rewarding StakingCredential
                   | Certifying DCert
  • Indicates the role (minting, spending, etc.) for lookup of the own input.


4 βš™οΈ Core Functions

4.1 πŸ”Ž findOwnInput

findOwnInput :: ScriptContext -> Maybe TxInInfo
  • Purpose: locates the TxInInfo corresponding to the current spending reference.

  • Logic: matches Spending txOutRef against txInfoInputs.

4.2 πŸ“‘ findDatum / findDatumHash

findDatum     :: DatumHash -> TxInfo -> Maybe Datum
findDatumHash :: Datum    -> TxInfo -> Maybe DatumHash
  • findDatum: looks up a datum by its hash in txInfoData.

  • findDatumHash: reverse-lookup of a datum value to its hash.

4.3 πŸ”— findTxInByTxOutRef

findTxInByTxOutRef :: TxOutRef -> TxInfo -> Maybe TxInInfo
  • Purpose: get the input information given its reference.

4.4 πŸ”„ findContinuingOutputs / getContinuingOutputs

findContinuingOutputs :: ScriptContext -> [Integer]
getContinuingOutputs  :: ScriptContext -> [TxOut]
  • findContinuingOutputs: indices of outputs at the same script address.

  • getContinuingOutputs: full TxOut values at that address.

  • Error: calls traceError if no own input found.

4.5 βœ… txSignedBy

txSignedBy :: TxInfo -> PubKeyHash -> Bool
  • Checks if a public key is among txInfoSignatories.

4.6 πŸ” ownHashes / ownHash

ownHashes :: ScriptContext -> (ValidatorHash, OutputDatum)
ownHash   :: ScriptContext -> ValidatorHash
  • Extracts the validator hash and attached datum for the current input.

  • ownHash: convenience returning only the validator hash.

4.7 πŸ” scriptOutputsAt

scriptOutputsAt :: ValidatorHash -> TxInfo -> [(OutputDatum, Value)]
  • Filters txInfoOutputs for those paying to a given validator.

4.8 πŸ’° valueLockedBy / valuePaidTo

valueLockedBy :: TxInfo -> ValidatorHash -> Value
valuePaidTo   :: TxInfo -> PubKeyHash     -> Value
  • valueLockedBy: sums values at script address.

  • valuePaidTo: sums values to a public key address.

4.9 πŸ’Έ valueSpent / valueProduced

valueSpent    :: TxInfo -> ValuealueProduced :: TxInfo -> Value
  • valueSpent: total of all inputs’ resolved txOutValue.

  • valueProduced: sum of all output values.

4.10 🏷️ spendsOutput

spendsOutput :: TxInfo -> TxId -> Integer -> Bool
  • Checks if any input matches a given (TxId, index) pair.


5 🀝 Typeclass Instances

  • Eq TxInInfo, Eq TxInfo, Eq ScriptContext:

    • V2 includes custom INLINABLE (==) on TxInfo to compare all fields, including maps.

  • Pretty instances for human-friendly debugging.


6 🏭 On-Chain Derivations

makeLift         ''TxInInfo
makeIsDataIndexed ''TxInInfo [('TxInInfo,0)]
makeLift         ''TxInfo
makeIsDataIndexed ''TxInfo   [('TxInfo,0)]
makeLift         ''ScriptContext
makeIsDataIndexed ''ScriptContext [('ScriptContext,0)]
  • makeLift and makeIsDataIndexed provide on-chain Lift and IsData instances for serialization.


7 πŸ“š Glossary

  • TxInInfo: input record pairing a reference and resolved output.

  • TxInfo: full transaction view available to validators, including redeemers and reference inputs.

  • ScriptContext: wraps TxInfo plus ScriptPurpose for the current script.

  • ScriptPurpose: reason code (e.g. Spending txOutRef, Minting cs).

  • OutputDatum: datum attached to a TxOut (could be inline or by hash).

  • Continuing outputs: new UTXOs at the same script address as the one being spent.

  • traceError: abort execution with an error message when invariants fail.

  • makeLift / makeIsDataIndexed: Template Haskell for on-chain data conversion.

Last updated