Plutus.V1.Ledger.Contexts
1. 📜 Overview
2. 🔧 LANGUAGE EXTENSIONS AND IMPORTS
3. 🗄️ Data Types
3.1 📥 TxInInfo
3.2 🎯 ScriptPurpose
3.3 📋 TxInfo
3.4 📜 ScriptContext
4. ⚙️ Utility Functions
4.1 🔍 findOwnInput
4.2 🔎 findDatum
4.3 🔖 findDatumHash
4.4 🔗 findTxInByTxOutRef
4.5 🔄 findContinuingOutputs
4.6 📥 getContinuingOutputs
4.7 ✔️ txSignedBy
4.8 🔑 pubKeyOutput
4.9 🧩 ownHashes
4.10 🏷️ ownHash
4.11 🔃 fromSymbol
4.12 🖋️ scriptOutputsAt
4.13 💰 valueLockedBy
4.14 💳 pubKeyOutputsAt
4.15 🏦 valuePaidTo
4.16 🔥 valueSpent
4.17 🏭 valueProduced
4.18 💱 ownCurrencySymbol
4.19 ⚔️ spendsOutput
5. 🤝 Typeclass Instances
6. 📚 Glossary
1 📜 Overview
The Plutus.V1.Ledger.Contexts
module defines the core types and helper functions for accessing transaction context within Plutus validators:
Data types:
TxInInfo
,ScriptPurpose
,TxInfo
,ScriptContext
capture inputs, outputs, and purpose of pending transactions.Utility functions to inspect and query components of the pending transaction (
findDatum
,valuePaidTo
, etc.).Typeclass instances for equality and pretty-printing, all marked
INLINABLE
or with compiler pragmas for on-chain use.
This tutorial explains the language pragmas/imports, each data type (fields, constructors), utility function (inputs, processing, outputs), and concludes with a glossary.
2 🔧 LANGUAGE EXTENSIONS AND 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-specialise #-}
{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}
module Plutus.V1.Ledger.Contexts where
import GHC.Generics (Generic)
import PlutusTx
import PlutusTx.Prelude
import Prettyprinter (Pretty(..), nest, viaShow, vsep, (<+>))
import Plutus.V1.Ledger.Address (Address(..), toPubKeyHash)
import Plutus.V1.Ledger.Credential (Credential(..), StakingCredential)
import Plutus.V1.Ledger.Crypto (PubKeyHash(..))
import Plutus.V1.Ledger.DCert (DCert(..))
import Plutus.V1.Ledger.Scripts
import Plutus.V1.Ledger.Time (POSIXTimeRange)
import Plutus.V1.Ledger.Tx (TxId(..), TxOut(..), TxOutRef(..))
import Plutus.V1.Ledger.Value (CurrencySymbol(..), Value)
import Prelude qualified as Haskell
Many
LANGUAGE
pragmas to support generics, deriving strategies, and on-chain requirements.OPTIONS_GHC to control inlining and interface pragmas.
Imports from
PlutusTx
and other ledger modules (Address
,Crypto
,Tx
,Value
).
3 🗄️ Data Types
3.1 📥 TxInInfo
data TxInInfo = TxInInfo
{ txInInfoOutRef :: TxOutRef
, txInInfoResolved :: TxOut
}
deriving stock (Generic, Haskell.Show, Haskell.Eq)
Fields:
txInInfoOutRef
: reference to the spent outputtxInInfoResolved
: fullTxOut
being consumed
Instances:
Custom
Eq
andPretty
defined below.
3.2 🎯 ScriptPurpose
data ScriptPurpose
= Minting CurrencySymbol
| Spending TxOutRef
| Rewarding StakingCredential
| Certifying DCert
deriving stock (Generic, Haskell.Show, Haskell.Eq)
Constructors: indicates why the script is running:
Minting
: forging tokensSpending
: consuming an outputRewarding
: distributing staking rewardsCertifying
: handling certificates
Custom
Eq
ensures on-chain pattern-matching equality.
3.3 📋 TxInfo
data TxInfo = TxInfo
{ txInfoInputs :: [TxInInfo]
, txInfoOutputs :: [TxOut]
, txInfoFee :: Value
, txInfoMint :: Value
, txInfoDCert :: [DCert]
, txInfoWdrl :: [(StakingCredential, Integer)]
, txInfoValidRange :: POSIXTimeRange
, txInfoSignatories :: [PubKeyHash]
, txInfoData :: [(DatumHash, Datum)]
, txInfoId :: TxId
}
deriving stock (Generic, Haskell.Show, Haskell.Eq)
Aggregates all relevant parts of the pending transaction as seen by a validator.
Custom
Eq
andPretty
defined below.
3.4 📜 ScriptContext
data ScriptContext = ScriptContext
{ scriptContextTxInfo :: TxInfo
, scriptContextPurpose :: ScriptPurpose
}
deriving stock (Generic, Haskell.Eq, Haskell.Show)
Wraps the full context passed to a validator: transaction info + its purpose.
Custom
Eq
andPretty
below.
4 ⚙️ Utility Functions
Each function is {-# INLINABLE #-}
for on-chain compilation.
4.1 🔍 findOwnInput
findOwnInput :: ScriptContext -> Maybe TxInInfo
Finds the
TxInInfo
corresponding to the output being validated whenpurpose = Spending
.Example: returns
Just
when matching input, elseNothing
.
4.2 🔎 findDatum
findDatum :: DatumHash -> TxInfo -> Maybe Datum
Searches
txInfoData
by hash, returns the associatedDatum
.
4.3 🔖 findDatumHash
findDatumHash :: Datum -> TxInfo -> Maybe DatumHash
Inverse of
findDatum
: finds the hash for a givenDatum
in the transaction.
4.4 🔗 findTxInByTxOutRef
findTxInByTxOutRef :: TxOutRef -> TxInfo -> Maybe TxInInfo
Lookup an input by its
TxOutRef
key intxInfoInputs
.
4.5 🔄 findContinuingOutputs
findContinuingOutputs :: ScriptContext -> [Integer]
Returns indices of outputs paying back to the same script address being validated.
Error (
traceError
) if no matching input found.
4.6 📥 getContinuingOutputs
getContinuingOutputs :: ScriptContext -> [TxOut]
Filters
txInfoOutputs
to those with the same script address as the input.
4.7 ✔️ txSignedBy
txSignedBy :: TxInfo -> PubKeyHash -> Bool
Checks if a given public key signed the transaction.
4.8 🔑 pubKeyOutput
pubKeyOutput :: TxOut -> Maybe PubKeyHash
Extracts the
PubKeyHash
locking aTxOut
, if present.
4.9 🧩 ownHashes
ownHashes :: ScriptContext -> (ValidatorHash, DatumHash)
Gets both the validator script hash and datum hash for the input being validated.
4.10 🏷️ ownHash
ownHash :: ScriptContext -> ValidatorHash
Extracts only the validator hash via
fst . ownHashes
.
4.11 🔃 fromSymbol
fromSymbol :: CurrencySymbol -> ValidatorHash
Converts a
CurrencySymbol
into aValidatorHash
.
4.12 🖋️ scriptOutputsAt
scriptOutputsAt :: ValidatorHash -> TxInfo -> [(DatumHash, Value)]
Collects outputs paying to a given script address.
4.13 💰 valueLockedBy
valueLockedBy :: TxInfo -> ValidatorHash -> Value
Sums the
Value
of all script outputs for a given hash.
4.14 💳 pubKeyOutputsAt
pubKeyOutputsAt :: PubKeyHash -> TxInfo -> [Value]
Lists values sent to a public key address.
4.15 🏦 valuePaidTo
valuePaidTo :: TxInfo -> PubKeyHash -> Value
Aggregates all outputs to a public key into one total
Value
.
4.16 🔥 valueSpent
valueSpent :: TxInfo -> Value
Sums the
Value
of inputs consumed by the transaction.
4.17 🏭 valueProduced
valueProduced :: TxInfo -> Value
Sums the
Value
of outputs created by the transaction.
4.18 💱 ownCurrencySymbol
ownCurrencySymbol :: ScriptContext -> CurrencySymbol
Returns the minting currency symbol when
purpose = Minting
.
4.19 ⚔️ spendsOutput
spendsOutput :: TxInfo -> TxId -> Integer -> Bool
Checks if the transaction spends a specific output by ID and index.
5 🤝 Typeclass Instances
instance Eq TxInInfo where
TxInInfo r1 o1 == TxInInfo r2 o2 = r1 == r2 && o1 == o2
instance Pretty TxInInfo where
pretty TxInInfo{txInInfoOutRef, txInInfoResolved} = pretty txInInfoOutRef <+> "->" <+> pretty txInInfoResolved
instance Eq ScriptPurpose where
{-# INLINABLE (==) #-}
... -- structural equality for each constructor
instance Pretty ScriptPurpose where
pretty = viaShow
instance Eq TxInfo where
{-# INLINABLE (==) #-}
... -- equality across all fields
instance Pretty TxInfo where
pretty TxInfo{...} = vsep [ ... ]
instance Eq ScriptContext where
{-# INLINABLE (==) #-}
ScriptContext i p == ScriptContext i' p' = i == i' && p == p'
instance Pretty ScriptContext where
pretty ScriptContext{scriptContextTxInfo, scriptContextPurpose} = vsep ["Purpose:" <+> pretty scriptContextPurpose, nest 2 $ vsep ["TxInfo:", pretty scriptContextTxInfo]]
makeLift ''TxInInfo
makeIsDataIndexed ''TxInInfo [('TxInInfo,0)]
makeLift ''TxInfo
makeIsDataIndexed ''TxInfo [('TxInfo,0)]
makeLift ''ScriptPurpose
makeIsDataIndexed ''ScriptPurpose [('Minting,0),('Spending,1),('Rewarding,2),('Certifying,3)]
makeLift ''ScriptContext
makeIsDataIndexed ''ScriptContext [('ScriptContext,0)]
6 📚 Glossary
TxInInfo: Input of a pending transaction (reference + resolved output).
ScriptPurpose: Why a validator is run (minting, spending, rewarding, certifying).
TxInfo: Summary of transaction inputs, outputs, fees, minting, certificates, and more.
ScriptContext: Full context passed to a validator:
TxInfo
+ScriptPurpose
.TxOutRef: Pointer to a transaction output (TxId + index).
Datum / DatumHash: Off-chain data attached to outputs.
CurrencySymbol: Identifier for a minted token.
INLINABLE / INLINE: Pragmas to control on-chain compilation and specialization.
makeLift / makeIsDataIndexed: Template Haskell for on-chain data serialization.
Last updated