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

Ledger.Tx.Constraints.OffChain

Synopsis

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

Constraints resolution

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 

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)))

tx :: Traversal' UnbalancedTx CardanoBuildTx Source #

txInsCollateral :: Lens' CardanoBuildTx [TxIn] Source #

txValidityRange :: Lens' CardanoBuildTx (TxValidityLowerBound BabbageEra, TxValidityUpperBound BabbageEra) Source #

txOuts :: Lens' CardanoBuildTx [TxOut] Source #

utxoIndex :: Lens' UnbalancedTx UtxoIndex Source #

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).

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.

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.

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.

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])))))))

_TypeCheckFailed :: AsMkTxError r => Prism' r ConnectionError Source #

_ToCardanoError :: AsMkTxError r => Prism' r ToCardanoError Source #

_TxOutRefNotFound :: AsMkTxError r => Prism' r TxOutRef Source #

_TxOutRefWrongType :: AsMkTxError r => Prism' r TxOutRef Source #

_TxOutRefNoReferenceScript :: AsMkTxError r => Prism' r TxOutRef Source #

_DatumNotFound :: AsMkTxError r => Prism' r DatumHash Source #

_DeclaredInputMismatch :: AsMkTxError r => Prism' r Value Source #

_MintingPolicyNotFound :: AsMkTxError r => Prism' r MintingPolicyHash Source #

_ScriptHashNotFound :: AsMkTxError r => Prism' r ScriptHash Source #

_TypedValidatorMissing :: AsMkTxError r => Prism' r () Source #

_DatumWrongHash :: AsMkTxError r => Prism' r (DatumHash, Datum) Source #

_CannotSatisfyAny :: AsMkTxError r => Prism' r () Source #

_NoMatchingOutputFound :: AsMkTxError r => Prism' r ValidatorHash Source #

_MultipleMatchingOutputsFound :: AsMkTxError r => Prism' r ValidatorHash Source #

Internals exposed for testing

data ValueSpentBalances Source #

The balances we track for computing the missing Value (if any) that needs to be added to the transaction. See note [Balance of value spent].

Constructors

ValueSpentBalances 

Fields

  • vbsRequired :: Value

    Required value spent by the transaction.

  • vbsProvided :: Value

    Value provided by an input or output of the transaction.

data ConstraintProcessingState Source #

Constructors

ConstraintProcessingState 

Fields

addOwnInput :: (MonadReader (ScriptLookups a) m, MonadError MkTxError m, FromData (DatumType a), ToData (DatumType a), ToData (RedeemerType a)) => ScriptInputConstraint (RedeemerType a) -> m TxConstraint Source #

Add a typed input, checking the type of the output it spends. Return the value of the spent output.

addOwnOutput :: (MonadReader (ScriptLookups a) m, MonadError MkTxError m, ToData (DatumType a)) => ScriptOutputConstraint (DatumType a) -> m TxConstraint Source #

Convert a ScriptOutputConstraint into a TxConstraint.

updateUtxoIndex :: (MonadReader (ScriptLookups a) m, MonadState ConstraintProcessingState m, MonadError MkTxError m) => m () Source #

lookupTxOutRef :: TxOutRef -> ReaderT (ScriptLookups a) (StateT ConstraintProcessingState (Except MkTxError)) DecoratedTxOut Source #

lookupMintingPolicy :: MintingPolicyHash -> ReaderT (ScriptLookups a) (StateT ConstraintProcessingState (Except MkTxError)) (Versioned MintingPolicy) Source #

lookupScript :: (MonadReader (ScriptLookups a) m, MonadError MkTxError m) => ScriptHash -> m (Versioned Script) Source #

lookupScriptAsReferenceScript :: Maybe ScriptHash -> ReaderT (ScriptLookups a) (StateT ConstraintProcessingState (Except MkTxError)) (ReferenceScript BabbageEra) Source #

prepareConstraints :: (FromData (DatumType a), ToData (DatumType a), ToData (RedeemerType a)) => [ScriptInputConstraint (RedeemerType a)] -> [ScriptOutputConstraint (DatumType a)] -> [TxConstraint] -> ReaderT (ScriptLookups a) (StateT ConstraintProcessingState (Except MkTxError)) SortedConstraints Source #

resolveScriptTxOut :: (MonadReader (ScriptLookups a) m, MonadError MkTxError m) => DecoratedTxOut -> m (Maybe (Versioned Validator, DatumWithOrigin, Value)) Source #

resolveScriptTxOutValidator :: (MonadReader (ScriptLookups a) m, MonadError MkTxError m) => DecoratedTxOut -> m (Maybe (Versioned Validator)) Source #

resolveScriptTxOutDatumAndValue :: (MonadReader (ScriptLookups a) m, MonadError MkTxError m) => DecoratedTxOut -> m (Maybe (DatumWithOrigin, Value)) Source #

data DatumWithOrigin Source #

Constructors

DatumInTx 

Fields

DatumInline 

Fields

checkValueSpent :: (MonadReader (ScriptLookups a) m, MonadState ConstraintProcessingState m, MonadError MkTxError m) => m () Source #