plutus-tx-constraints-1.2.0.0: Plutus Transaction Constraints
Safe HaskellNone
LanguageHaskell2010

Ledger.Tx.Constraints

Description

Constraints for transactions

Synopsis

Documentation

This module defines TxConstraints, a list of constraints on transactions. To construct a value of TxConstraints use the mustPayToTheScriptWithDatumHash, mustSpendAtLeast, etc functions. Once we have a TxConstraints value it can be used both to generate a transaction that satisfies the constraints (off-chain, using mkTx) and to check whether a given pending transaction meets the constraints (on-chain, using checkScriptContext, checkScriptContext).

data TxConstraints i o Source #

Restrictions placed on the allocation of funds to outputs of transactions.

Instances

Instances details
Bifunctor TxConstraints Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Methods

bimap :: (a -> b) -> (c -> d) -> TxConstraints a c -> TxConstraints b d Source #

first :: (a -> b) -> TxConstraints a c -> TxConstraints b c Source #

second :: (b -> c) -> TxConstraints a b -> TxConstraints a c Source #

(Show i, Show o) => Show (TxConstraints i o) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Generic (TxConstraints i o) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Associated Types

type Rep (TxConstraints i o) :: Type -> Type Source #

Methods

from :: TxConstraints i o -> Rep (TxConstraints i o) x Source #

to :: Rep (TxConstraints i o) x -> TxConstraints i o Source #

Semigroup (TxConstraints i o) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Monoid (TxConstraints i o) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

(FromJSON i, FromJSON o) => FromJSON (TxConstraints i o) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Methods

parseJSON :: Value -> Parser (TxConstraints i o)

parseJSONList :: Value -> Parser [TxConstraints i o]

(ToJSON i, ToJSON o) => ToJSON (TxConstraints i o) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Methods

toJSON :: TxConstraints i o -> Value

toEncoding :: TxConstraints i o -> Encoding

toJSONList :: [TxConstraints i o] -> Value

toEncodingList :: [TxConstraints i o] -> Encoding

Monoid (TxConstraints i o) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Methods

mempty :: TxConstraints i o

Semigroup (TxConstraints i o) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Methods

(<>) :: TxConstraints i o -> TxConstraints i o -> TxConstraints i o

type Rep (TxConstraints i o) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

type Rep (TxConstraints i o) = D1 ('MetaData "TxConstraints" "Ledger.Tx.Constraints.TxConstraints" "plutus-tx-constraints-1.2.0.0-9U3hMxZSaNH217R0XsdS0A" 'False) (C1 ('MetaCons "TxConstraints" 'PrefixI 'True) ((S1 ('MetaSel ('Just "txConstraints") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxConstraint]) :*: S1 ('MetaSel ('Just "txConstraintFuns") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxConstraintFuns)) :*: (S1 ('MetaSel ('Just "txOwnInputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ScriptInputConstraint i]) :*: S1 ('MetaSel ('Just "txOwnOutputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [ScriptOutputConstraint o]))))

data TxConstraint Source #

Constraints on transactions that want to spend script outputs

Constructors

MustIncludeDatumInTxWithHash DatumHash Datum

The provided DatumHash and Datum must be included in the transaction body. Like MustIncludeDatumInTx, but useful when you already have a DatumHash and want to make sure that is is the actual hash of the Datum.

MustIncludeDatumInTx Datum

Like MustHashDatum, but the hash of the Datum is computed automatically.

MustValidateInTimeRange !(ValidityInterval POSIXTime)

The transaction's validity range must be set with the given POSIXTimeRange.

MustBeSignedBy PaymentPubKeyHash

The transaction must add the given PaymentPubKeyHash in its signatories.

MustSpendAtLeast Value

The sum of the transaction's input Values must be at least as much as the given Value.

MustProduceAtLeast Value

The sum of the transaction's output Values must be at least as much as the given Value.

MustSpendPubKeyOutput TxOutRef

The transaction must spend the given unspent transaction public key output.

MustSpendScriptOutput TxOutRef Redeemer (Maybe TxOutRef)

The transaction must spend the given unspent transaction script output.

MustUseOutputAsCollateral TxOutRef

The transaction must include the utxo as collateral input.

MustReferenceOutput TxOutRef

The transaction must reference (not spend) the given unspent transaction output.

MustMintValue MintingPolicyHash Redeemer TokenName Integer (Maybe TxOutRef)

The transaction must mint the given token and amount.

MustPayToAddress Address (Maybe (TxOutDatum Datum)) (Maybe ScriptHash) Value

The transaction must create a transaction output.

MustSatisfyAnyOf [[TxConstraint]]

The transaction must satisfy constraints given as an alternative of conjuctions (DNF), that is `check (MustSatisfyAnyOf xs) = any (all check) xs`

Instances

Instances details
Eq TxConstraint Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Show TxConstraint Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Generic TxConstraint Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Associated Types

type Rep TxConstraint :: Type -> Type Source #

FromJSON TxConstraint Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Methods

parseJSON :: Value -> Parser TxConstraint

parseJSONList :: Value -> Parser [TxConstraint]

ToJSON TxConstraint Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Methods

toJSON :: TxConstraint -> Value

toEncoding :: TxConstraint -> Encoding

toJSONList :: [TxConstraint] -> Value

toEncodingList :: [TxConstraint] -> Encoding

Pretty TxConstraint Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Methods

pretty :: TxConstraint -> Doc ann

prettyList :: [TxConstraint] -> Doc ann

type Rep TxConstraint Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

type Rep TxConstraint = D1 ('MetaData "TxConstraint" "Ledger.Tx.Constraints.TxConstraints" "plutus-tx-constraints-1.2.0.0-9U3hMxZSaNH217R0XsdS0A" 'False) (((C1 ('MetaCons "MustIncludeDatumInTxWithHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatumHash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Datum)) :+: (C1 ('MetaCons "MustIncludeDatumInTx" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Datum)) :+: C1 ('MetaCons "MustValidateInTimeRange" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 (ValidityInterval POSIXTime))))) :+: (C1 ('MetaCons "MustBeSignedBy" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 PaymentPubKeyHash)) :+: (C1 ('MetaCons "MustSpendAtLeast" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)) :+: C1 ('MetaCons "MustProduceAtLeast" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))))) :+: ((C1 ('MetaCons "MustSpendPubKeyOutput" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef)) :+: (C1 ('MetaCons "MustSpendScriptOutput" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Redeemer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxOutRef)))) :+: C1 ('MetaCons "MustUseOutputAsCollateral" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef)))) :+: ((C1 ('MetaCons "MustReferenceOutput" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef)) :+: C1 ('MetaCons "MustMintValue" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MintingPolicyHash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Redeemer)) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TokenName) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxOutRef)))))) :+: (C1 ('MetaCons "MustPayToAddress" 'PrefixI 'False) ((S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Address) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (TxOutDatum Datum)))) :*: (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ScriptHash)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))) :+: C1 ('MetaCons "MustSatisfyAnyOf" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [[TxConstraint]]))))))

data ScriptInputConstraint a Source #

Constraint which specifies that the transaction must spend a transaction output from a target script.

Constructors

ScriptInputConstraint 

Fields

Instances

Instances details
Functor ScriptInputConstraint Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Eq a => Eq (ScriptInputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Show a => Show (ScriptInputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Generic (ScriptInputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Associated Types

type Rep (ScriptInputConstraint a) :: Type -> Type Source #

FromJSON a => FromJSON (ScriptInputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Methods

parseJSON :: Value -> Parser (ScriptInputConstraint a)

parseJSONList :: Value -> Parser [ScriptInputConstraint a]

ToJSON a => ToJSON (ScriptInputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Pretty a => Pretty (ScriptInputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Methods

pretty :: ScriptInputConstraint a -> Doc ann

prettyList :: [ScriptInputConstraint a] -> Doc ann

type Rep (ScriptInputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

type Rep (ScriptInputConstraint a) = D1 ('MetaData "ScriptInputConstraint" "Ledger.Tx.Constraints.TxConstraints" "plutus-tx-constraints-1.2.0.0-9U3hMxZSaNH217R0XsdS0A" 'False) (C1 ('MetaCons "ScriptInputConstraint" 'PrefixI 'True) (S1 ('MetaSel ('Just "icRedeemer") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "icTxOutRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef) :*: S1 ('MetaSel ('Just "icReferenceTxOutRef") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe TxOutRef)))))

data ScriptOutputConstraint a Source #

Constructors

ScriptOutputConstraint 

Fields

Instances

Instances details
Functor ScriptOutputConstraint Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Eq a => Eq (ScriptOutputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Show a => Show (ScriptOutputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Generic (ScriptOutputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Associated Types

type Rep (ScriptOutputConstraint a) :: Type -> Type Source #

FromJSON a => FromJSON (ScriptOutputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Methods

parseJSON :: Value -> Parser (ScriptOutputConstraint a)

parseJSONList :: Value -> Parser [ScriptOutputConstraint a]

ToJSON a => ToJSON (ScriptOutputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Pretty a => Pretty (ScriptOutputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

Methods

pretty :: ScriptOutputConstraint a -> Doc ann

prettyList :: [ScriptOutputConstraint a] -> Doc ann

type Rep (ScriptOutputConstraint a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.TxConstraints

type Rep (ScriptOutputConstraint a) = D1 ('MetaData "ScriptOutputConstraint" "Ledger.Tx.Constraints.TxConstraints" "plutus-tx-constraints-1.2.0.0-9U3hMxZSaNH217R0XsdS0A" 'False) (C1 ('MetaCons "ScriptOutputConstraint" 'PrefixI 'True) (S1 ('MetaSel ('Just "ocDatum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (TxOutDatum a)) :*: (S1 ('MetaSel ('Just "ocValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value) :*: S1 ('MetaSel ('Just "ocReferenceScriptHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ScriptHash)))))

Defining constraints

mustPayToTheScriptWithDatumHash :: o -> Value -> TxConstraints i o Source #

mustPayToTheScriptWithDatumHash d v locks the value v with a script alongside a datum d which is included in the transaction body.

If used in OffChain, this constraint creates a script output with dt and vl and adds dt in the transaction's datum witness set. The script address is derived from the typed validator that is provided in the ScriptLookups with typedValidatorLookups.

If used in OnChain, this constraint verifies that d is part of the datum witness set and that the new script transaction output with dt and vt is part of the transaction's outputs.

mustPayToAddress :: forall i o. Address -> Value -> TxConstraints i o Source #

mustPayToAddress addr v locks the value v at the given address addr.

If used in OffChain, this constraint creates a script output with addr and v.

If used in OnChain, this constraint verifies that the script transaction output with addr and v is part of the transaction's outputs.

mustPayToAddressWithDatumHash :: forall i o. Address -> Datum -> Value -> TxConstraints i o Source #

mustPayToAddress addr d v locks the value v at the given address addr alonside a datum d.

If used in OffChain, this constraint creates a script output with addr, d and v and adds d in the transaction's datum witness set.

If used in OnChain, this constraint verifies that d is part of the datum witness set and that the script transaction output with addr, d and v is part of the transaction's outputs.

mustPayToAddressWithDatumInTx :: forall i o. Address -> Datum -> Value -> TxConstraints i o Source #

mustPayToAddressWithDatumInTx addr d v locks the value v at the given address addr alonside a datum d.

If used in OffChain, this constraint creates a script output with addr, d and v and adds d in the transaction's datum witness set.

If used in OnChain, this constraint verifies that d is part of the datum witness set and that the script transaction output with addr, d and v as part of the transaction's outputs.

mustPayToAddressWithInlineDatum :: forall i o. Address -> Datum -> Value -> TxConstraints i o Source #

mustPayToAddressWithInlineDatum vh d v is the same as mustPayToAddress, but with an inline datum.

mustPayToAddressWithReferenceScript :: forall i o. Address -> ScriptHash -> Maybe (TxOutDatum Datum) -> Value -> TxConstraints i o Source #

mustPayToAddressWithReferenceScript addr scriptHash d v creates a transaction output with an reference script. This allows the script to be used as a reference script.

If used in OffChain, this constraint creates an output with addr, scriptHash, d and v and maybe adds d in the transaction's datum witness set.

If used in OnChain, this constraint verifies that d is part of the datum witness set and that the transaction output with addr, scriptHash, d and v is part of the transaction's outputs.

mustPayToAddressWithReferenceValidator :: forall i o. Address -> ValidatorHash -> Maybe (TxOutDatum Datum) -> Value -> TxConstraints i o Source #

mustPayToAddressWithReferenceValidator is a helper that calls mustPayToAddressWithReferenceScript.

mustPayToAddressWithReferenceMintingPolicy :: forall i o. Address -> MintingPolicyHash -> Maybe (TxOutDatum Datum) -> Value -> TxConstraints i o Source #

mustPayToAddressWithReferenceMintingPolicy is a helper that calls mustPayToAddressWithReferenceScript.

mustMintCurrency :: forall i o. MintingPolicyHash -> TokenName -> Integer -> TxConstraints i o Source #

Same as mustMintCurrencyWithRedeemer, but sets the redeemer to the unit redeemer.

mustMintCurrencyWithRedeemer :: forall i o. MintingPolicyHash -> Redeemer -> TokenName -> Integer -> TxConstraints i o Source #

Same as mustMintCurrencyWithRedeemerAndReference, but sets the reference to Nothing.

mustMintValue :: forall i o. Value -> TxConstraints i o Source #

Same as mustMintValueWithRedeemer, but sets the redeemer to the unit redeemer.

mustMintValueWithRedeemer :: forall i o. Redeemer -> Value -> TxConstraints i o Source #

Same as mustMintValueWithRedeemerAndReference, but sets the reference to Nothing.

mustSpendAtLeast :: forall i o. Value -> TxConstraints i o Source #

mustSpendAtLeast v requires the sum of the transaction's inputs value to be at least v.

If used in OffChain, this constraint checks if at least the given value is spent in the transaction. When the transaction is created, a DeclaredInputMismatch error is raised if it is not the case.

If used in OnChain, this constraint verifies that the sum of the transaction's inputs value to be at least v.

mustSpendPubKeyOutput :: forall i o. TxOutRef -> TxConstraints i o Source #

mustSpendPubKeyOutput utxo must spend the given unspent transaction public key output.

If used in OffChain, this constraint adds utxo as an input to the transaction. Information about this utxo must be provided in the ScriptLookups with unspentOutputs.

If several calls to mustSpendPubKeyOutput are performed for the same TxOutRef, only one instance of the constraint is kept when the transaction is created.

If used in OnChain, this constraint verifies that the transaction spends this utxo.

mustSpendOutputFromTheScript :: TxOutRef -> i -> TxConstraints i o Source #

mustSpendOutputFromTheScript txOutRef red spends the transaction output txOutRef with a script address using the redeemer red.

If used in OffChain, this constraint spends a script output txOutRef with redeemer red. The script address is derived from the typed validator that is provided in the ScriptLookups with typedValidatorLookups.

If used in OnChain, this constraint verifies that the spend script transaction output with red is part of the transaction's inputs.

mustSpendOutputFromTheReferencedScript :: TxOutRef -> i -> TxOutRef -> TxConstraints i o Source #

mustSpendOutputFromTheReferencedScript txOutRef red ref spends the transaction output txOutRef with a script address using the redeemer red, using the reference script ref as a validator.

If used in OffChain, this constraint spends a script output txOutRef with redeemer red. The script address is derived from the typed validator that is provided in the ScriptLookups with typedValidatorLookups.

If used in OnChain, this constraint verifies that the spend script transaction output with red is part of the transaction's inputs.

mustSpendScriptOutput :: forall i o. TxOutRef -> Redeemer -> TxConstraints i o Source #

mustSpendScriptOutput utxo red must spend the given unspent transaction script output.

If used in OffChain, this constraint adds utxo and red as an input to the transaction. Information about this utxo must be provided in the ScriptLookups with unspentOutputs. The validator must be either provided by unspentOutputs or through otherScript . The datum must be either provided by unspentOutputs or through otherData.

If several calls to mustSpendScriptOutput are performed for the same TxOutRef, if the two constraints have different redeemers, an error will be thrown when the transaction is created. Otherwise, only one instance of the constraint is kept. If combined with mustSpendScriptOutputWithReference for the same TxOutRef, see mustSpendScriptOutputWithReference.

If used in OnChain, this constraint verifies that the transaction spends this utxo.

mustSpendScriptOutputWithReference :: TxOutRef -> Redeemer -> TxOutRef -> TxConstraints i o Source #

mustSpendScriptOutputWithReference utxo red refTxOutref must spend the given unspent transaction script output, using a script reference as witness.

If used in OffChain, this constraint adds utxo and red as an input to the transaction, and refTxOutref as reference input. Information about utxo and refTxOutref must be provided in the ScriptLookups with unspentOutputs. The datum must be either provided by unspentOutputs or through otherData.

If several calls to mustSpendScriptOutputWithReference are performed for the same TxOutRef, if the two constraints have different redeemers, or if the two constraints use a different TxOutRef as a TxOutRef, an error will be thrown when the transaction is created. Otherwise, only one instance of the constraint is kept.

If combined with mustSpendScriptOutput for the same TxOutRef, an error is throw if they have a different redeemer. Otherwise, only one instance of the mustSpendScriptOutputWithReference constraint is kept, the mustSpendScriptOutput constraints are ignored.

If used in OnChain, this constraint verifies that the transaction spends this utxo.

mustSpendScriptOutputWithMatchingDatumAndValue :: forall i o. ValidatorHash -> (Datum -> Bool) -> (Value -> Bool) -> Redeemer -> TxConstraints i o Source #

mustSpendScriptOutputWithMatchingDatumAndValue validatorHash datumPredicate valuePredicate redeemer must spend an output locked by the given validator script hash, which includes a Datum that matches the given datum predicate and a Value that matches the given value predicate.

If used in OffChain, this constraint checks that there's exactly one output that matches the requirements, and then adds this as an input to the transaction with the given redeemer.

The outputs that will be considered need to be privided in the ScriptLookups with unspentOutputs.

If used in OnChain, this constraint verifies that there's at least one input that matches the requirements.

mustUseOutputAsCollateral :: forall i o. TxOutRef -> TxConstraints i o Source #

mustUseOutputAsCollateral utxo must use the given unspent transaction output reference as collateral input.

If used in OffChain, this constraint adds utxo as a collateral input to the transaction.

In OnChain this constraint has no effect, since no information about collateral inputs is passed to the scripts.

mustReferenceOutput :: forall i o. TxOutRef -> TxConstraints i o Source #

mustReferenceOutput utxo must reference (not spend!) the given unspent transaction output reference.

If used in OffChain, this constraint adds utxo as a reference input to the transaction.

If used in OnChain, this constraint verifies that the transaction references this utxo.

mustValidateInSlotRange :: forall i o. ValidityInterval Slot -> TxConstraints i o Source #

mustValidateInSlotRange r requires the transaction's validity slot range to be contained in Slot range r.

If used in OffChain, this constraint sets the transaction's validity slot range to r.

If used in OnChain, this constraint verifies that the slot range r is entirely contained in the transaction's validity time range.

mustValidateInTimeRange :: forall i o. ValidityInterval POSIXTime -> TxConstraints i o Source #

mustValidateInTimeRange r requires the transaction's validity time range to be contained in POSIXTime range r.

If used in OffChain, this constraint sets the transaction's validity time range to r.

If used in OnChain, this constraint verifies that the time range r is entirely contained in the transaction's validity time range.

mustBeSignedBy :: forall i o. PaymentPubKeyHash -> TxConstraints i o Source #

mustBeSignedBy pk requires the transaction to be signed by the public key pk.

If used in OffChain, this constraint adds pk in the transaction's public key witness set.

If used in OnChain, this constraint verifies that pk is part of the transaction's public key witness set.

mustProduceAtLeast :: forall i o. Value -> TxConstraints i o Source #

mustProduceAtLeast v requires the sum of the transaction's outputs value to be at least v.

If used in OffChain, this constraint checks if at least the given value is produced in the transaction. When the transaction is created, a DeclaredOutputMismatch error is raised if it is not the case.

If used in OnChain, this constraint verifies that the sum of the transaction's outputs value to be at least v.

mustIncludeDatumInTxWithHash :: DatumHash -> Datum -> TxConstraints i o Source #

mustIncludeDatumInTxWithHash dh d requires the transaction body to include the datum hash dh and actual datum d.

If used in OffChain, this constraint adds dh and d in the transaction's body.

If used in OnChain, this constraint verifies that dh and d are part of the transaction's body.

mustIncludeDatumInTx :: forall i o. Datum -> TxConstraints i o Source #

mustIncludeDatumInTx d requires the transaction body to include the datum d.

If used in OffChain, this constraint adds d in the transaction's body alongside it's hash (which is computed automatically).

If used in OnChain, this constraint verifies that d is part of the transaction's body.

Must-pay constraints for specific types of addresses

mustPayToPubKey :: forall i o. PaymentPubKeyHash -> Value -> TxConstraints i o Source #

mustPayToPubKey pkh v is the same as mustPayToPubKeyAddressWithDatumHash, but without any staking key hash and datum.

mustPayToPubKeyAddress :: forall i o. PaymentPubKeyHash -> StakingCredential -> Value -> TxConstraints i o Source #

mustPayToPubKeyAddress pkh skh v is the same as mustPayToPubKeyAddressWithDatumHash, but without any datum.

mustPayToPubKeyWithDatumHash :: forall i o. PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o Source #

mustPayToPubKeyWithDatumHash pkh d v is the same as mustPayToPubKeyAddressWithDatumHash, but without the staking key hash.

mustPayToPubKeyAddressWithDatumHash :: forall i o. PaymentPubKeyHash -> StakingCredential -> Datum -> Value -> TxConstraints i o Source #

mustPayToPubKeyAddressWithDatumHash pkh skh d v locks a transaction output with a public key address.

If used in OffChain, this constraint creates a public key output with pkh, skh, d and v and maybe adds d in the transaction's datum witness set.

If used in OnChain, this constraint verifies that d is part of the datum witness set and that the public key transaction output with pkh, skh, d and v is part of the transaction's outputs.

mustPayToPubKeyWithDatumInTx :: forall i o. PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o Source #

mustPayToPubKeyWithDatumInTx pkh d v is the same as mustPayToPubKeyAddressWithDatumHash, but with an inline datum and without the staking key hash.

mustPayToPubKeyAddressWithDatumInTx :: forall i o. PaymentPubKeyHash -> StakingCredential -> Datum -> Value -> TxConstraints i o Source #

mustPayToPubKeyAddressWithDatumInTx pkh d v is the same as mustPayToPubKeyAddressWithDatumHash, but the datum is also added in the transaction body.

mustPayToPubKeyWithInlineDatum :: forall i o. PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o Source #

mustPayToPubKeyWithInlineDatum pkh d v is the same as mustPayToPubKeyAddressWithDatumHash, but with an inline datum and without the staking key hash.

mustPayToPubKeyAddressWithInlineDatum :: forall i o. PaymentPubKeyHash -> StakingCredential -> Datum -> Value -> TxConstraints i o Source #

mustPayWithInlineInlineDatumToPubKeyAddress pkh d v is the same as mustPayToPubKeyAddressWithInlineDatum, but the datum is inline in the Tx.

mustPayToOtherScriptWithDatumHash :: forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o Source #

mustPayToOtherScriptWithDatumHash vh d v is the same as mustPayToOtherScriptAddressWithDatumHash, but without the staking key hash.

mustPayToOtherScriptWithDatumInTx :: forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o Source #

mustPayToOtherScriptWithDatumInTx vh d v is the same as mustPayToOtherScriptAddressWithDatumHash, but without the staking key hash.

mustPayToOtherScriptWithInlineDatum :: forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o Source #

mustPayToOtherScriptWithInlineDatum vh d v is the same as mustPayToOtherScriptAddressWithDatumHash, but with an inline datum and without the staking key hash.

mustPayToOtherScriptAddressWithDatumHash :: forall i o. ValidatorHash -> StakingCredential -> Datum -> Value -> TxConstraints i o Source #

mustPayToOtherScriptAddressWithDatumHash vh svh d v locks the value v with the given script hash vh alonside a datum d.

If used in OffChain, this constraint creates a script output with vh, svh, d and v and adds d in the transaction's datum witness set.

If used in OnChain, this constraint verifies that d is part of the datum witness set and that the script transaction output with vh, svh, d and v is part of the transaction's outputs. For v, this means that the transactions output must be at least the given value. The output can contain more, or different tokens, but the requested value v must be present.

mustPayToOtherScriptAddressWithDatumInTx :: forall i o. ValidatorHash -> StakingCredential -> Datum -> Value -> TxConstraints i o Source #

mustPayToOtherScriptAddressWithDatumInTx vh svh d v locks the value v with the given script hash vh alonside a datum d.

If used in OffChain, this constraint creates a script output with vh, svh, d and v and adds d in the transaction's datum witness set.

If used in OnChain, this constraint verifies that d is part of the datum witness set and that the script transaction output with vh, svh, d and v is part of the transaction's outputs. For v, this means that the transactions output must be at least the given value. The output can contain more, or different tokens, but the requested value v must be present.

mustPayToOtherScriptAddressWithInlineDatum :: forall i o. ValidatorHash -> StakingCredential -> Datum -> Value -> TxConstraints i o Source #

mustPayToOtherScriptAddressInlineDatum vh d v is the same as mustPayToOtherScriptAddressWithDatumHash, but with an inline datum.

Defining off-chain only constraints

spendUtxosFromPlutusV1Script :: Map Address (Map TxOutRef DecoratedTxOut) -> Validator -> Redeemer -> UntypedConstraints Source #

A set of constraints for a transaction that collects PlutusV1 script outputs from the address of the given validator script, using the same redeemer script for all outputs.

spendUtxosFromPlutusV1ScriptFilter :: (TxOutRef -> DecoratedTxOut -> Bool) -> Map Address (Map TxOutRef DecoratedTxOut) -> Validator -> Redeemer -> UntypedConstraints Source #

spendUtxosFromTheScriptFilter :: forall i o. (TxOutRef -> DecoratedTxOut -> Bool) -> Map TxOutRef DecoratedTxOut -> i -> TxConstraints i o Source #

Given the pay to script address of the Validator, collect from it all the outputs that match a predicate, using the RedeemerValue.

spendUtxosFromTheScript :: forall i o. Map TxOutRef DecoratedTxOut -> i -> TxConstraints i o Source #

A version of spendUtxosFromScript that selects all outputs at the address

spendUtxosFromTheReferencedScript :: forall i o. Map TxOutRef DecoratedTxOut -> i -> TxOutRef -> TxConstraints i o Source #

A version of spendUtxosFromScript that selects all outputs at the address

utxo the set of utxos we search into to find the one we want to spendsOutput ref the reference to the utxo that contains the reference script

spendUtxosFromPlutusV2Script :: Map Address (Map TxOutRef DecoratedTxOut) -> Validator -> Redeemer -> UntypedConstraints Source #

A set of constraints for a transaction that collects PlutusV2 script outputs from the address of the given validator script, using the same redeemer script for all outputs.

spendUtxosFromPlutusV2ScriptFilter :: (TxOutRef -> DecoratedTxOut -> Bool) -> Map Address (Map TxOutRef DecoratedTxOut) -> Validator -> Redeemer -> UntypedConstraints Source #

Queries on constraints

modifiesUtxoSet :: forall i o. TxConstraints i o -> Bool Source #

Check whether every transaction that satisfies the constraints has to modify the UTXO set.

isSatisfiable :: forall i o. TxConstraints i o -> Bool Source #

Are the constraints satisfiable?

Off-chain transaction generation

data UnbalancedTx Source #

An unbalanced transaction. It needs to be balanced and signed before it can be submitted to the ledger. See note [Submitting transactions from Plutus contracts] in Wallet.

Constructors

UnbalancedCardanoTx 

Fields

Instances

Instances details
Eq UnbalancedTx Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Show UnbalancedTx Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Generic UnbalancedTx Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Associated Types

type Rep UnbalancedTx :: Type -> Type Source #

FromJSON UnbalancedTx Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Methods

parseJSON :: Value -> Parser UnbalancedTx

parseJSONList :: Value -> Parser [UnbalancedTx]

ToJSON UnbalancedTx Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Methods

toJSON :: UnbalancedTx -> Value

toEncoding :: UnbalancedTx -> Encoding

toJSONList :: [UnbalancedTx] -> Value

toEncodingList :: [UnbalancedTx] -> Encoding

Pretty UnbalancedTx Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Methods

pretty :: UnbalancedTx -> Doc ann

prettyList :: [UnbalancedTx] -> Doc ann

type Rep UnbalancedTx Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

type Rep UnbalancedTx = D1 ('MetaData "UnbalancedTx" "Ledger.Tx.Constraints.OffChain" "plutus-tx-constraints-1.2.0.0-9U3hMxZSaNH217R0XsdS0A" 'False) (C1 ('MetaCons "UnbalancedCardanoTx" 'PrefixI 'True) (S1 ('MetaSel ('Just "unBalancedCardanoBuildTx") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 CardanoBuildTx) :*: S1 ('MetaSel ('Just "unBalancedTxUtxoIndex") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UtxoIndex)))

data MkTxError Source #

Constructors

TypeCheckFailed ConnectionError 
ToCardanoError ToCardanoError 
TxOutRefNotFound TxOutRef 
TxOutRefWrongType TxOutRef 
TxOutRefNoReferenceScript TxOutRef 
DatumNotFound DatumHash 
DeclaredInputMismatch Value 
DeclaredOutputMismatch Value 
MintingPolicyNotFound MintingPolicyHash 
ScriptHashNotFound ScriptHash 
TypedValidatorMissing 
DatumWrongHash DatumHash Datum 
CannotSatisfyAny 
NoMatchingOutputFound ValidatorHash 
MultipleMatchingOutputsFound ValidatorHash 
AmbiguousRedeemer TxOutRef [Redeemer] 
AmbiguousReferenceScript TxOutRef [TxOutRef] 

Instances

Instances details
Eq MkTxError Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Show MkTxError Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Generic MkTxError Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Associated Types

type Rep MkTxError :: Type -> Type Source #

FromJSON MkTxError Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Methods

parseJSON :: Value -> Parser MkTxError

parseJSONList :: Value -> Parser [MkTxError]

ToJSON MkTxError Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Methods

toJSON :: MkTxError -> Value

toEncoding :: MkTxError -> Encoding

toJSONList :: [MkTxError] -> Value

toEncodingList :: [MkTxError] -> Encoding

Pretty MkTxError Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Methods

pretty :: MkTxError -> Doc ann

prettyList :: [MkTxError] -> Doc ann

type Rep MkTxError Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

type Rep MkTxError = D1 ('MetaData "MkTxError" "Ledger.Tx.Constraints.OffChain" "plutus-tx-constraints-1.2.0.0-9U3hMxZSaNH217R0XsdS0A" 'False) ((((C1 ('MetaCons "TypeCheckFailed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ConnectionError)) :+: C1 ('MetaCons "ToCardanoError" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ToCardanoError))) :+: (C1 ('MetaCons "TxOutRefNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef)) :+: C1 ('MetaCons "TxOutRefWrongType" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef)))) :+: ((C1 ('MetaCons "TxOutRefNoReferenceScript" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef)) :+: C1 ('MetaCons "DatumNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatumHash))) :+: (C1 ('MetaCons "DeclaredInputMismatch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value)) :+: C1 ('MetaCons "DeclaredOutputMismatch" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Value))))) :+: (((C1 ('MetaCons "MintingPolicyNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 MintingPolicyHash)) :+: C1 ('MetaCons "ScriptHashNotFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ScriptHash))) :+: (C1 ('MetaCons "TypedValidatorMissing" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "DatumWrongHash" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 DatumHash) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Datum)))) :+: ((C1 ('MetaCons "CannotSatisfyAny" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "NoMatchingOutputFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValidatorHash))) :+: (C1 ('MetaCons "MultipleMatchingOutputsFound" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValidatorHash)) :+: (C1 ('MetaCons "AmbiguousRedeemer" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Redeemer])) :+: C1 ('MetaCons "AmbiguousReferenceScript" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 TxOutRef) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [TxOutRef])))))))

mkTx :: (FromData (DatumType a), ToData (DatumType a), ToData (RedeemerType a)) => Params -> ScriptLookups a -> TxConstraints (RedeemerType a) (DatumType a) -> Either MkTxError UnbalancedTx Source #

Turn a TxConstraints value into an unbalanced transaction that satisfies the constraints. To use this in a contract, see submitTxConstraints and related functions.

adjustUnbalancedTx :: PParams -> UnbalancedTx -> ([Lovelace], UnbalancedTx) Source #

Each transaction output should contain a minimum amount of Ada (this is a restriction on the real Cardano network).

Combining multiple typed scripts into one transaction

data SomeLookupsAndConstraints where Source #

Some typed TxConstraints and the ScriptLookups needed to turn them into an UnbalancedTx.

Constructors

SomeLookupsAndConstraints :: forall a. (FromData (DatumType a), ToData (DatumType a), ToData (RedeemerType a)) => ScriptLookups a -> TxConstraints (RedeemerType a) (DatumType a) -> SomeLookupsAndConstraints 

mkSomeTx :: Params -> [SomeLookupsAndConstraints] -> Either MkTxError UnbalancedTx Source #

Given a list of SomeLookupsAndConstraints describing the constraints for several scripts, build a single transaction that runs all the scripts.

mkTxWithParams :: (FromData (DatumType a), ToData (DatumType a), ToData (RedeemerType a)) => Params -> ScriptLookups a -> TxConstraints (RedeemerType a) (DatumType a) -> Either MkTxError UnbalancedTx Source #

Turn a TxConstraints value into an unbalanced transaction that satisfies the constraints. To use this in a contract, see submitTxConstraints and related functions.

Lookups

data ScriptLookups a Source #

Constructors

ScriptLookups 

Fields

Instances

Instances details
Show (ScriptLookups a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Generic (ScriptLookups a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Associated Types

type Rep (ScriptLookups a) :: Type -> Type Source #

Semigroup (ScriptLookups a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Monoid (ScriptLookups a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

FromJSON (ScriptLookups a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Methods

parseJSON :: Value -> Parser (ScriptLookups a)

parseJSONList :: Value -> Parser [ScriptLookups a]

ToJSON (ScriptLookups a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

Methods

toJSON :: ScriptLookups a -> Value

toEncoding :: ScriptLookups a -> Encoding

toJSONList :: [ScriptLookups a] -> Value

toEncodingList :: [ScriptLookups a] -> Encoding

type Rep (ScriptLookups a) Source # 
Instance details

Defined in Ledger.Tx.Constraints.OffChain

type Rep (ScriptLookups a) = D1 ('MetaData "ScriptLookups" "Ledger.Tx.Constraints.OffChain" "plutus-tx-constraints-1.2.0.0-9U3hMxZSaNH217R0XsdS0A" 'False) (C1 ('MetaCons "ScriptLookups" 'PrefixI 'True) ((S1 ('MetaSel ('Just "slTxOutputs") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map TxOutRef DecoratedTxOut)) :*: (S1 ('MetaSel ('Just "slOtherScripts") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map ScriptHash (Versioned Script))) :*: S1 ('MetaSel ('Just "slOtherData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Map DatumHash Datum)))) :*: ((S1 ('MetaSel ('Just "slPaymentPubKeyHashes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Set PaymentPubKeyHash)) :*: S1 ('MetaSel ('Just "slTypedValidator") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (TypedValidator a)))) :*: (S1 ('MetaSel ('Just "slOwnPaymentPubKeyHash") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe PaymentPubKeyHash)) :*: S1 ('MetaSel ('Just "slOwnStakingCredential") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe StakingCredential))))))

typedValidatorLookups :: TypedValidator a -> ScriptLookups a Source #

A script lookups value with a script instance. For convenience this also includes the minting policy script that forwards all checks to the instance's validator.

If called multiple times, only the first typed validator is kept:

typedValidatorLookups tv1 <> typedValidatorLookups tv2 <> ...
    == typedValidatorLookups tv1

unspentOutputs :: Map TxOutRef DecoratedTxOut -> ScriptLookups a Source #

A script lookups value that uses the map of unspent outputs to resolve input constraints.

mintingPolicy :: Versioned MintingPolicy -> ScriptLookups a Source #

A script lookups value with a versioned minting policy script.

plutusV1MintingPolicy :: MintingPolicy -> ScriptLookups a Source #

A script lookups value with a PlutusV1 minting policy script.

plutusV2MintingPolicy :: MintingPolicy -> ScriptLookups a Source #

A script lookups value with a PlutusV2 minting policy script.

otherScript :: Versioned Validator -> ScriptLookups a Source #

A script lookups value with a versioned validator script.

plutusV1OtherScript :: Validator -> ScriptLookups a Source #

A script lookups value with a PlutusV1 validator script.

plutusV2OtherScript :: Validator -> ScriptLookups a Source #

A script lookups value with a PlutusV2 validator script.

otherData :: Datum -> ScriptLookups a Source #

A script lookups value with a datum.

paymentPubKey :: PaymentPubKey -> ScriptLookups a Source #

A script lookups value with a payment public key

paymentPubKeyHash :: PaymentPubKeyHash -> ScriptLookups a Source #

A script lookups value with a payment public key

Deprecated

mustPayToTheScript :: o -> Value -> TxConstraints i o Source #

Deprecated: Use mustPayToTheScriptWithDatumHash instead

mustPayToAddressWithDatum :: forall i o. Address -> Datum -> Value -> TxConstraints i o Source #

Deprecated: Use mustPayToAddressWithDatumHash instead

mustPayWithDatumToPubKey :: forall i o. PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o Source #

Deprecated: Use mustPayToPubKeyWithDatumHash instead

mustPayWithDatumToPubKeyAddress :: forall i o. PaymentPubKeyHash -> StakingCredential -> Datum -> Value -> TxConstraints i o Source #

Deprecated: Use mustPayToPubKeyAddressWithDatumHash instead

mustPayWithDatumInTxToPubKey :: forall i o. PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o Source #

Deprecated: Use mustPayToPubKeyWithDatumInTx instead

mustPayWithDatumInTxToPubKeyAddress :: forall i o. PaymentPubKeyHash -> StakingCredential -> Datum -> Value -> TxConstraints i o Source #

Deprecated: Use mustPayToPubKeyAddressWithDatumInTx instead

mustPayWithInlineDatumToPubKey :: forall i o. PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o Source #

Deprecated: Use mustPayToPubKeyWithInlineDatum instead

mustPayWithInlineDatumToPubKeyAddress :: forall i o. PaymentPubKeyHash -> StakingCredential -> Datum -> Value -> TxConstraints i o Source #

Deprecated: Use mustPayToPubKeyAddressWithInlineDatum instead

mustPayToOtherScript :: forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o Source #

Deprecated: Use mustPayToOtherScriptWithDatumHash instead

mustPayToOtherScriptAddress :: forall i o. ValidatorHash -> StakingCredential -> Datum -> Value -> TxConstraints i o Source #

Deprecated: Use mustPayToOtherScriptAddressWithDatumHash instead

mustValidateIn :: forall i o. POSIXTimeRange -> TxConstraints i o Source #

Deprecated: Please use mustValidateInTimeRange or mustValidateInSlotRange instead

mustValidateIn r requires the transaction's validity time range to be contained in POSIXTimeRange r.

If used in OffChain, this constraint sets the transaction's validity time range to r.

If used in OnChain, this constraint verifies that the time range r is entirely contained in the transaction's validity time range.