Safe Haskell | None |
---|---|
Language | Haskell2010 |
Constraints for transactions
Synopsis
- data TxConstraints i o = TxConstraints {}
- data TxConstraint
- = MustIncludeDatumInTxWithHash DatumHash Datum
- | MustIncludeDatumInTx Datum
- | MustValidateInTimeRange !(ValidityInterval POSIXTime)
- | MustBeSignedBy PaymentPubKeyHash
- | MustSpendAtLeast Value
- | MustProduceAtLeast Value
- | MustSpendPubKeyOutput TxOutRef
- | MustSpendScriptOutput TxOutRef Redeemer (Maybe TxOutRef)
- | MustUseOutputAsCollateral TxOutRef
- | MustReferenceOutput TxOutRef
- | MustMintValue MintingPolicyHash Redeemer TokenName Integer (Maybe TxOutRef)
- | MustPayToAddress Address (Maybe (TxOutDatum Datum)) (Maybe ScriptHash) Value
- | MustSatisfyAnyOf [[TxConstraint]]
- data ScriptInputConstraint a = ScriptInputConstraint {
- icRedeemer :: a
- icTxOutRef :: TxOutRef
- icReferenceTxOutRef :: Maybe TxOutRef
- data ScriptOutputConstraint a = ScriptOutputConstraint {
- ocDatum :: TxOutDatum a
- ocValue :: Value
- ocReferenceScriptHash :: Maybe ScriptHash
- mustPayToTheScriptWithDatumHash :: o -> Value -> TxConstraints i o
- mustPayToTheScriptWithDatumInTx :: o -> Value -> TxConstraints i o
- mustPayToTheScriptWithInlineDatum :: o -> Value -> TxConstraints i o
- mustPayToTheScriptWithReferenceScript :: ScriptHash -> TxOutDatum o -> Value -> TxConstraints i o
- mustPayToAddress :: forall i o. Address -> Value -> TxConstraints i o
- mustPayToAddressWithDatumHash :: forall i o. Address -> Datum -> Value -> TxConstraints i o
- mustPayToAddressWithDatumInTx :: forall i o. Address -> Datum -> Value -> TxConstraints i o
- mustPayToAddressWithInlineDatum :: forall i o. Address -> Datum -> Value -> TxConstraints i o
- mustPayToAddressWithReferenceScript :: forall i o. Address -> ScriptHash -> Maybe (TxOutDatum Datum) -> Value -> TxConstraints i o
- mustPayToAddressWithReferenceValidator :: forall i o. Address -> ValidatorHash -> Maybe (TxOutDatum Datum) -> Value -> TxConstraints i o
- mustPayToAddressWithReferenceMintingPolicy :: forall i o. Address -> MintingPolicyHash -> Maybe (TxOutDatum Datum) -> Value -> TxConstraints i o
- mustMintCurrency :: forall i o. MintingPolicyHash -> TokenName -> Integer -> TxConstraints i o
- mustMintCurrencyWithRedeemer :: forall i o. MintingPolicyHash -> Redeemer -> TokenName -> Integer -> TxConstraints i o
- mustMintValue :: forall i o. Value -> TxConstraints i o
- mustMintValueWithRedeemer :: forall i o. Redeemer -> Value -> TxConstraints i o
- mustSpendAtLeast :: forall i o. Value -> TxConstraints i o
- mustSpendPubKeyOutput :: forall i o. TxOutRef -> TxConstraints i o
- mustSpendOutputFromTheScript :: TxOutRef -> i -> TxConstraints i o
- mustSpendOutputFromTheReferencedScript :: TxOutRef -> i -> TxOutRef -> TxConstraints i o
- mustSpendScriptOutput :: forall i o. TxOutRef -> Redeemer -> TxConstraints i o
- mustSpendScriptOutputWithReference :: TxOutRef -> Redeemer -> TxOutRef -> TxConstraints i o
- mustSpendScriptOutputWithMatchingDatumAndValue :: forall i o. ValidatorHash -> (Datum -> Bool) -> (Value -> Bool) -> Redeemer -> TxConstraints i o
- mustUseOutputAsCollateral :: forall i o. TxOutRef -> TxConstraints i o
- mustReferenceOutput :: forall i o. TxOutRef -> TxConstraints i o
- mustValidateInSlotRange :: forall i o. ValidityInterval Slot -> TxConstraints i o
- mustValidateInTimeRange :: forall i o. ValidityInterval POSIXTime -> TxConstraints i o
- mustBeSignedBy :: forall i o. PaymentPubKeyHash -> TxConstraints i o
- mustProduceAtLeast :: forall i o. Value -> TxConstraints i o
- mustIncludeDatumInTxWithHash :: DatumHash -> Datum -> TxConstraints i o
- mustIncludeDatumInTx :: forall i o. Datum -> TxConstraints i o
- mustSatisfyAnyOf :: forall i o. [TxConstraints i o] -> TxConstraints i o
- mustPayToPubKey :: forall i o. PaymentPubKeyHash -> Value -> TxConstraints i o
- mustPayToPubKeyAddress :: forall i o. PaymentPubKeyHash -> StakingCredential -> Value -> TxConstraints i o
- mustPayToPubKeyWithDatumHash :: forall i o. PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
- mustPayToPubKeyAddressWithDatumHash :: forall i o. PaymentPubKeyHash -> StakingCredential -> Datum -> Value -> TxConstraints i o
- mustPayToPubKeyWithDatumInTx :: forall i o. PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
- mustPayToPubKeyAddressWithDatumInTx :: forall i o. PaymentPubKeyHash -> StakingCredential -> Datum -> Value -> TxConstraints i o
- mustPayToPubKeyWithInlineDatum :: forall i o. PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
- mustPayToPubKeyAddressWithInlineDatum :: forall i o. PaymentPubKeyHash -> StakingCredential -> Datum -> Value -> TxConstraints i o
- mustPayToOtherScriptWithDatumHash :: forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o
- mustPayToOtherScriptWithDatumInTx :: forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o
- mustPayToOtherScriptWithInlineDatum :: forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o
- mustPayToOtherScriptAddressWithDatumHash :: forall i o. ValidatorHash -> StakingCredential -> Datum -> Value -> TxConstraints i o
- mustPayToOtherScriptAddressWithDatumInTx :: forall i o. ValidatorHash -> StakingCredential -> Datum -> Value -> TxConstraints i o
- mustPayToOtherScriptAddressWithInlineDatum :: forall i o. ValidatorHash -> StakingCredential -> Datum -> Value -> TxConstraints i o
- spendUtxosFromPlutusV1Script :: Map Address (Map TxOutRef DecoratedTxOut) -> Validator -> Redeemer -> UntypedConstraints
- spendUtxosFromPlutusV1ScriptFilter :: (TxOutRef -> DecoratedTxOut -> Bool) -> Map Address (Map TxOutRef DecoratedTxOut) -> Validator -> Redeemer -> UntypedConstraints
- spendUtxosFromTheScriptFilter :: forall i o. (TxOutRef -> DecoratedTxOut -> Bool) -> Map TxOutRef DecoratedTxOut -> i -> TxConstraints i o
- spendUtxosFromTheScript :: forall i o. Map TxOutRef DecoratedTxOut -> i -> TxConstraints i o
- spendUtxosFromTheReferencedScript :: forall i o. Map TxOutRef DecoratedTxOut -> i -> TxOutRef -> TxConstraints i o
- spendUtxosFromPlutusV2Script :: Map Address (Map TxOutRef DecoratedTxOut) -> Validator -> Redeemer -> UntypedConstraints
- spendUtxosFromPlutusV2ScriptFilter :: (TxOutRef -> DecoratedTxOut -> Bool) -> Map Address (Map TxOutRef DecoratedTxOut) -> Validator -> Redeemer -> UntypedConstraints
- modifiesUtxoSet :: forall i o. TxConstraints i o -> Bool
- isSatisfiable :: forall i o. TxConstraints i o -> Bool
- data UnbalancedTx = UnbalancedCardanoTx {
- unBalancedCardanoBuildTx :: CardanoBuildTx
- unBalancedTxUtxoIndex :: UtxoIndex
- data MkTxError
- = 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]
- mkTx :: (FromData (DatumType a), ToData (DatumType a), ToData (RedeemerType a)) => Params -> ScriptLookups a -> TxConstraints (RedeemerType a) (DatumType a) -> Either MkTxError UnbalancedTx
- adjustUnbalancedTx :: PParams -> UnbalancedTx -> ([Lovelace], UnbalancedTx)
- data SomeLookupsAndConstraints where
- 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
- mkTxWithParams :: (FromData (DatumType a), ToData (DatumType a), ToData (RedeemerType a)) => Params -> ScriptLookups a -> TxConstraints (RedeemerType a) (DatumType a) -> Either MkTxError UnbalancedTx
- data ScriptLookups a = ScriptLookups {
- slTxOutputs :: Map TxOutRef DecoratedTxOut
- slOtherScripts :: Map ScriptHash (Versioned Script)
- slOtherData :: Map DatumHash Datum
- slPaymentPubKeyHashes :: Set PaymentPubKeyHash
- slTypedValidator :: Maybe (TypedValidator a)
- slOwnPaymentPubKeyHash :: Maybe PaymentPubKeyHash
- slOwnStakingCredential :: Maybe StakingCredential
- typedValidatorLookups :: TypedValidator a -> ScriptLookups a
- unspentOutputs :: Map TxOutRef DecoratedTxOut -> ScriptLookups a
- mintingPolicy :: Versioned MintingPolicy -> ScriptLookups a
- plutusV1MintingPolicy :: MintingPolicy -> ScriptLookups a
- plutusV2MintingPolicy :: MintingPolicy -> ScriptLookups a
- otherScript :: Versioned Validator -> ScriptLookups a
- plutusV1OtherScript :: Validator -> ScriptLookups a
- plutusV2OtherScript :: Validator -> ScriptLookups a
- otherData :: Datum -> ScriptLookups a
- paymentPubKey :: PaymentPubKey -> ScriptLookups a
- paymentPubKeyHash :: PaymentPubKeyHash -> ScriptLookups a
- mustPayToTheScript :: o -> Value -> TxConstraints i o
- mustPayToAddressWithDatum :: forall i o. Address -> Datum -> Value -> TxConstraints i o
- mustPayWithDatumToPubKey :: forall i o. PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
- mustPayWithDatumToPubKeyAddress :: forall i o. PaymentPubKeyHash -> StakingCredential -> Datum -> Value -> TxConstraints i o
- mustPayWithDatumInTxToPubKey :: forall i o. PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
- mustPayWithDatumInTxToPubKeyAddress :: forall i o. PaymentPubKeyHash -> StakingCredential -> Datum -> Value -> TxConstraints i o
- mustPayWithInlineDatumToPubKey :: forall i o. PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
- mustPayWithInlineDatumToPubKeyAddress :: forall i o. PaymentPubKeyHash -> StakingCredential -> Datum -> Value -> TxConstraints i o
- mustPayToOtherScript :: forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o
- mustPayToOtherScriptAddress :: forall i o. ValidatorHash -> StakingCredential -> Datum -> Value -> TxConstraints i o
- mustValidateIn :: forall i o. POSIXTimeRange -> TxConstraints i o
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
data TxConstraint Source #
Constraints on transactions that want to spend script outputs
MustIncludeDatumInTxWithHash DatumHash Datum | The provided |
MustIncludeDatumInTx Datum | Like |
MustValidateInTimeRange !(ValidityInterval POSIXTime) | The transaction's validity range must be set with the given |
MustBeSignedBy PaymentPubKeyHash | The transaction must add the given |
MustSpendAtLeast Value | The sum of the transaction's input |
MustProduceAtLeast Value | The sum of the transaction's output |
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
data ScriptInputConstraint a Source #
Constraint which specifies that the transaction must spend a transaction output from a target script.
ScriptInputConstraint | |
|
Instances
data ScriptOutputConstraint a Source #
ScriptOutputConstraint | |
|
Instances
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.
mustPayToTheScriptWithDatumInTx :: o -> Value -> TxConstraints i o Source #
mustPayToTheScriptWithInlineDatum :: o -> Value -> TxConstraints i o Source #
mustPayToTheScriptWithReferenceScript :: ScriptHash -> TxOutDatum o -> Value -> TxConstraints i o Source #
mustPayToAddress :: forall i o. Address -> Value -> TxConstraints i o Source #
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 #
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 #
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 #
mustIncludeDatumInTx :: forall i o. Datum -> TxConstraints i o Source #
mustSatisfyAnyOf :: forall i o. [TxConstraints i o] -> TxConstraints i o Source #
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
.
UnbalancedCardanoTx | |
|
Instances
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
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
.
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 #
ScriptLookups | |
|
Instances
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.