{-# LANGUAGE DeriveAnyClass       #-}
{-# LANGUAGE DeriveGeneric        #-}
{-# LANGUAGE DerivingStrategies   #-}
{-# LANGUAGE FlexibleContexts     #-}
{-# LANGUAGE FlexibleInstances    #-}
{-# LANGUAGE LambdaCase           #-}
{-# LANGUAGE MonoLocalBinds       #-}
{-# LANGUAGE NamedFieldPuns       #-}
{-# LANGUAGE NoImplicitPrelude    #-}
{-# LANGUAGE OverloadedStrings    #-}
{-# LANGUAGE UndecidableInstances #-}

{-# OPTIONS_GHC -Wno-simplifiable-class-constraints #-}
{-# OPTIONS_GHC -fno-specialise #-}
{-# OPTIONS_GHC -fno-ignore-interface-pragmas #-}
{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}

-- | Constraints for transactions
module Ledger.Tx.Constraints.TxConstraints where

import Cardano.Node.Emulator.TimeSlot (slotRangeToPOSIXTimeRange)
import Data.Aeson (FromJSON (parseJSON), ToJSON (toJSON))
import Data.Aeson qualified as Aeson
import Data.Bifunctor (Bifunctor (bimap))
import Data.Default (def)
import Data.Map (Map)
import Data.Map qualified as Map
import GHC.Generics (Generic)
import Prettyprinter (Pretty (pretty, prettyList), defaultLayoutOptions, hang, layoutPretty, viaShow, vsep, (<+>))

import PlutusTx qualified
import PlutusTx.AssocMap qualified as AssocMap
import PlutusTx.Prelude (Bool (False, True), Eq, Foldable (foldMap), Functor (fmap), Integer, JoinSemiLattice ((\/)),
                         Maybe (Just, Nothing), Monoid (mempty), Semigroup ((<>)), any, concat, foldl, map, mapMaybe,
                         not, null, ($), (.), (==), (>>=), (||))

import Ledger.Address (Address (Address), PaymentPubKeyHash (PaymentPubKeyHash))
import Ledger.Slot (Slot)
import Ledger.Tx (DecoratedTxOut)
import Plutus.Script.Utils.V1.Address qualified as PV1
import Plutus.Script.Utils.V2.Address qualified as PV2
import Plutus.V1.Ledger.Api (Credential (PubKeyCredential, ScriptCredential), Datum, DatumHash, MintingPolicyHash,
                             POSIXTime, POSIXTimeRange, Redeemer, StakingCredential, TxOutRef, Validator, ValidatorHash)
import Plutus.V1.Ledger.Interval qualified as I
import Plutus.V1.Ledger.Scripts (MintingPolicyHash (MintingPolicyHash), ScriptHash (ScriptHash),
                                 ValidatorHash (ValidatorHash), unitRedeemer)
import Plutus.V1.Ledger.Value (TokenName, Value, isZero)
import Plutus.V1.Ledger.Value qualified as Value

import Control.Lens (At (at), (^.))
import Data.Function (const, flip)
import Data.Maybe (fromMaybe)
import Prelude qualified as Haskell
import Prettyprinter.Render.String (renderShowS)

import Ledger.Tx.Constraints.ValidityInterval (ValidityInterval, fromPlutusInterval, toPlutusInterval)

-- | How tx outs datum are embedded in a a Tx
--
-- We do not use 'TxOutDatum' from cardano-node to provide easier to handel
-- type (we don't type witnesses) and to have a distinction at the type leve
-- between constraints that require a Datum and constraints (like
-- 'MustPayToOtherScript') with an optional datum (like
-- 'MustPayToPubKeyAddress').
data TxOutDatum datum =
    TxOutDatumHash datum
    -- ^ A datum specified in a transaction output using only it's hash, i.e.
    -- the datum is not inlined nor is it added in the transaction body.
  | TxOutDatumInTx datum
    -- ^ A datum specified in a transaction output using it's hash, while also
    -- adding the actual datum in the transaction body.
  | TxOutDatumInline datum
    -- ^ A datum inlined in a transaction output. It is *not* added in the
    -- transaction body.
    deriving stock (Int -> TxOutDatum datum -> ShowS
[TxOutDatum datum] -> ShowS
TxOutDatum datum -> String
(Int -> TxOutDatum datum -> ShowS)
-> (TxOutDatum datum -> String)
-> ([TxOutDatum datum] -> ShowS)
-> Show (TxOutDatum datum)
forall datum. Show datum => Int -> TxOutDatum datum -> ShowS
forall datum. Show datum => [TxOutDatum datum] -> ShowS
forall datum. Show datum => TxOutDatum datum -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxOutDatum datum] -> ShowS
$cshowList :: forall datum. Show datum => [TxOutDatum datum] -> ShowS
show :: TxOutDatum datum -> String
$cshow :: forall datum. Show datum => TxOutDatum datum -> String
showsPrec :: Int -> TxOutDatum datum -> ShowS
$cshowsPrec :: forall datum. Show datum => Int -> TxOutDatum datum -> ShowS
Haskell.Show, (forall x. TxOutDatum datum -> Rep (TxOutDatum datum) x)
-> (forall x. Rep (TxOutDatum datum) x -> TxOutDatum datum)
-> Generic (TxOutDatum datum)
forall x. Rep (TxOutDatum datum) x -> TxOutDatum datum
forall x. TxOutDatum datum -> Rep (TxOutDatum datum) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall datum x. Rep (TxOutDatum datum) x -> TxOutDatum datum
forall datum x. TxOutDatum datum -> Rep (TxOutDatum datum) x
$cto :: forall datum x. Rep (TxOutDatum datum) x -> TxOutDatum datum
$cfrom :: forall datum x. TxOutDatum datum -> Rep (TxOutDatum datum) x
Generic, TxOutDatum datum -> TxOutDatum datum -> Bool
(TxOutDatum datum -> TxOutDatum datum -> Bool)
-> (TxOutDatum datum -> TxOutDatum datum -> Bool)
-> Eq (TxOutDatum datum)
forall datum.
Eq datum =>
TxOutDatum datum -> TxOutDatum datum -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxOutDatum datum -> TxOutDatum datum -> Bool
$c/= :: forall datum.
Eq datum =>
TxOutDatum datum -> TxOutDatum datum -> Bool
== :: TxOutDatum datum -> TxOutDatum datum -> Bool
$c== :: forall datum.
Eq datum =>
TxOutDatum datum -> TxOutDatum datum -> Bool
Haskell.Eq, a -> TxOutDatum b -> TxOutDatum a
(a -> b) -> TxOutDatum a -> TxOutDatum b
(forall a b. (a -> b) -> TxOutDatum a -> TxOutDatum b)
-> (forall a b. a -> TxOutDatum b -> TxOutDatum a)
-> Functor TxOutDatum
forall a b. a -> TxOutDatum b -> TxOutDatum a
forall a b. (a -> b) -> TxOutDatum a -> TxOutDatum b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> TxOutDatum b -> TxOutDatum a
$c<$ :: forall a b. a -> TxOutDatum b -> TxOutDatum a
fmap :: (a -> b) -> TxOutDatum a -> TxOutDatum b
$cfmap :: forall a b. (a -> b) -> TxOutDatum a -> TxOutDatum b
Haskell.Functor)
    deriving anyclass ([TxOutDatum datum] -> Encoding
[TxOutDatum datum] -> Value
TxOutDatum datum -> Encoding
TxOutDatum datum -> Value
(TxOutDatum datum -> Value)
-> (TxOutDatum datum -> Encoding)
-> ([TxOutDatum datum] -> Value)
-> ([TxOutDatum datum] -> Encoding)
-> ToJSON (TxOutDatum datum)
forall datum. ToJSON datum => [TxOutDatum datum] -> Encoding
forall datum. ToJSON datum => [TxOutDatum datum] -> Value
forall datum. ToJSON datum => TxOutDatum datum -> Encoding
forall datum. ToJSON datum => TxOutDatum datum -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TxOutDatum datum] -> Encoding
$ctoEncodingList :: forall datum. ToJSON datum => [TxOutDatum datum] -> Encoding
toJSONList :: [TxOutDatum datum] -> Value
$ctoJSONList :: forall datum. ToJSON datum => [TxOutDatum datum] -> Value
toEncoding :: TxOutDatum datum -> Encoding
$ctoEncoding :: forall datum. ToJSON datum => TxOutDatum datum -> Encoding
toJSON :: TxOutDatum datum -> Value
$ctoJSON :: forall datum. ToJSON datum => TxOutDatum datum -> Value
ToJSON, Value -> Parser [TxOutDatum datum]
Value -> Parser (TxOutDatum datum)
(Value -> Parser (TxOutDatum datum))
-> (Value -> Parser [TxOutDatum datum])
-> FromJSON (TxOutDatum datum)
forall datum. FromJSON datum => Value -> Parser [TxOutDatum datum]
forall datum. FromJSON datum => Value -> Parser (TxOutDatum datum)
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TxOutDatum datum]
$cparseJSONList :: forall datum. FromJSON datum => Value -> Parser [TxOutDatum datum]
parseJSON :: Value -> Parser (TxOutDatum datum)
$cparseJSON :: forall datum. FromJSON datum => Value -> Parser (TxOutDatum datum)
FromJSON)

instance Eq d => Eq (TxOutDatum d) where
    TxOutDatumHash d
d1 == :: TxOutDatum d -> TxOutDatum d -> Bool
== TxOutDatumHash d
d2     = d
d1 d -> d -> Bool
forall a. Eq a => a -> a -> Bool
== d
d2
    TxOutDatumInTx d
d1 == TxOutDatumInTx d
d2     = d
d1 d -> d -> Bool
forall a. Eq a => a -> a -> Bool
== d
d2
    TxOutDatumInline d
d1 == TxOutDatumInline d
d2 = d
d1 d -> d -> Bool
forall a. Eq a => a -> a -> Bool
== d
d2
    TxOutDatum d
_ == TxOutDatum d
_                                     = Bool
False

instance Functor TxOutDatum where
    fmap :: (a -> b) -> TxOutDatum a -> TxOutDatum b
fmap a -> b
f (TxOutDatumHash a
d)   = b -> TxOutDatum b
forall datum. datum -> TxOutDatum datum
TxOutDatumHash (b -> TxOutDatum b) -> b -> TxOutDatum b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
d
    fmap a -> b
f (TxOutDatumInTx a
d)   = b -> TxOutDatum b
forall datum. datum -> TxOutDatum datum
TxOutDatumInTx (b -> TxOutDatum b) -> b -> TxOutDatum b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
d
    fmap a -> b
f (TxOutDatumInline a
d) = b -> TxOutDatum b
forall datum. datum -> TxOutDatum datum
TxOutDatumInline (b -> TxOutDatum b) -> b -> TxOutDatum b
forall a b. (a -> b) -> a -> b
$ a -> b
f a
d

getTxOutDatum :: TxOutDatum d -> d
getTxOutDatum :: TxOutDatum d -> d
getTxOutDatum (TxOutDatumHash d
d)   = d
d
getTxOutDatum (TxOutDatumInTx d
d)   = d
d
getTxOutDatum (TxOutDatumInline d
d) = d
d

isTxOutDatumHash :: TxOutDatum d -> Bool
isTxOutDatumHash :: TxOutDatum d -> Bool
isTxOutDatumHash (TxOutDatumHash d
_) = Bool
True
isTxOutDatumHash TxOutDatum d
_                  = Bool
False

isTxOutDatumInTx :: TxOutDatum d -> Bool
isTxOutDatumInTx :: TxOutDatum d -> Bool
isTxOutDatumInTx (TxOutDatumInTx d
_) = Bool
True
isTxOutDatumInTx TxOutDatum d
_                  = Bool
False

isTxOutDatumInline :: TxOutDatum d -> Bool
isTxOutDatumInline :: TxOutDatum d -> Bool
isTxOutDatumInline (TxOutDatumInline d
_) = Bool
True
isTxOutDatumInline TxOutDatum d
_                    = Bool
False

instance Pretty d => Pretty (TxOutDatum d) where
  pretty :: TxOutDatum d -> Doc ann
pretty = \case
    TxOutDatumHash d
d   -> Doc ann
"hashed datum" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> d -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty d
d
    TxOutDatumInTx d
d   -> Doc ann
"datum in tx body" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> d -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty d
d
    TxOutDatumInline d
d -> Doc ann
"inline datum" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> d -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty d
d

-- | Constraints on transactions that want to spend script outputs
data TxConstraint =
      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 'Value's must be at least as much as
    -- the given 'Value'.
    | MustProduceAtLeast Value
    -- ^ The sum of the transaction's output 'Value's 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`
    deriving stock (Int -> TxConstraint -> ShowS
[TxConstraint] -> ShowS
TxConstraint -> String
(Int -> TxConstraint -> ShowS)
-> (TxConstraint -> String)
-> ([TxConstraint] -> ShowS)
-> Show TxConstraint
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxConstraint] -> ShowS
$cshowList :: [TxConstraint] -> ShowS
show :: TxConstraint -> String
$cshow :: TxConstraint -> String
showsPrec :: Int -> TxConstraint -> ShowS
$cshowsPrec :: Int -> TxConstraint -> ShowS
Haskell.Show, (forall x. TxConstraint -> Rep TxConstraint x)
-> (forall x. Rep TxConstraint x -> TxConstraint)
-> Generic TxConstraint
forall x. Rep TxConstraint x -> TxConstraint
forall x. TxConstraint -> Rep TxConstraint x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxConstraint x -> TxConstraint
$cfrom :: forall x. TxConstraint -> Rep TxConstraint x
Generic, TxConstraint -> TxConstraint -> Bool
(TxConstraint -> TxConstraint -> Bool)
-> (TxConstraint -> TxConstraint -> Bool) -> Eq TxConstraint
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TxConstraint -> TxConstraint -> Bool
$c/= :: TxConstraint -> TxConstraint -> Bool
== :: TxConstraint -> TxConstraint -> Bool
$c== :: TxConstraint -> TxConstraint -> Bool
Haskell.Eq)
    deriving anyclass ([TxConstraint] -> Encoding
[TxConstraint] -> Value
TxConstraint -> Encoding
TxConstraint -> Value
(TxConstraint -> Value)
-> (TxConstraint -> Encoding)
-> ([TxConstraint] -> Value)
-> ([TxConstraint] -> Encoding)
-> ToJSON TxConstraint
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [TxConstraint] -> Encoding
$ctoEncodingList :: [TxConstraint] -> Encoding
toJSONList :: [TxConstraint] -> Value
$ctoJSONList :: [TxConstraint] -> Value
toEncoding :: TxConstraint -> Encoding
$ctoEncoding :: TxConstraint -> Encoding
toJSON :: TxConstraint -> Value
$ctoJSON :: TxConstraint -> Value
ToJSON, Value -> Parser [TxConstraint]
Value -> Parser TxConstraint
(Value -> Parser TxConstraint)
-> (Value -> Parser [TxConstraint]) -> FromJSON TxConstraint
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [TxConstraint]
$cparseJSONList :: Value -> Parser [TxConstraint]
parseJSON :: Value -> Parser TxConstraint
$cparseJSON :: Value -> Parser TxConstraint
FromJSON)

instance Pretty TxConstraint where
    pretty :: TxConstraint -> Doc ann
pretty = \case
        MustIncludeDatumInTxWithHash DatumHash
dvh Datum
dv ->
            Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"must include datum in tx with hash:", DatumHash -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty DatumHash
dvh, Datum -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Datum
dv]
        MustIncludeDatumInTx Datum
dv ->
            Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"must include datum in tx:", Datum -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Datum
dv]
        MustValidateInTimeRange ValidityInterval POSIXTime
range ->
            Doc ann
"must validate in:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> ValidityInterval POSIXTime -> Doc ann
forall a ann. Show a => a -> Doc ann
viaShow ValidityInterval POSIXTime
range
        MustBeSignedBy PaymentPubKeyHash
signatory ->
            Doc ann
"must be signed by:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> PaymentPubKeyHash -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty PaymentPubKeyHash
signatory
        MustSpendAtLeast Value
vl ->
            Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"must spend at least:", Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Value
vl]
        MustProduceAtLeast Value
vl ->
            Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"must produce at least:", Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Value
vl]
        MustSpendPubKeyOutput TxOutRef
ref ->
            Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"must spend pubkey output:", TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOutRef
ref]
        MustSpendScriptOutput TxOutRef
ref Redeemer
red Maybe TxOutRef
mref ->
            Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"must spend script output:", TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOutRef
ref, Redeemer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Redeemer
red, Maybe TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Maybe TxOutRef
mref]
        MustReferenceOutput TxOutRef
ref ->
            Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"must reference output:", TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOutRef
ref]
        MustMintValue MintingPolicyHash
mps Redeemer
red TokenName
tn Integer
i Maybe TxOutRef
mref ->
            Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"must mint value:", MintingPolicyHash -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty MintingPolicyHash
mps, Redeemer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Redeemer
red, TokenName -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TokenName
tn Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Integer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Integer
i, Maybe TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Maybe TxOutRef
mref]
        MustPayToAddress Address
addr Maybe (TxOutDatum Datum)
datum Maybe ScriptHash
refScript Value
v ->
            Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"must pay to pubkey address:", Address -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Address
addr, Maybe (TxOutDatum Datum) -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Maybe (TxOutDatum Datum)
datum, Maybe ScriptHash -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Maybe ScriptHash
refScript, Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Value
v]
        MustUseOutputAsCollateral TxOutRef
ref ->
            Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"must use output as collateral:", TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOutRef
ref]
        MustSatisfyAnyOf [[TxConstraint]]
xs ->
            Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"must satisfy any of:", [[TxConstraint]] -> Doc ann
forall a ann. Pretty a => [a] -> Doc ann
prettyList [[TxConstraint]]
xs]


-- | Constraints on transactions that contain functions. These don't support conversion to and from JSON.
data TxConstraintFun =
    MustSpendScriptOutputWithMatchingDatumAndValue ValidatorHash (Datum -> Bool) (Value -> Bool) Redeemer
    -- ^ The transaction must spend a script output from the given script address which matches the @Datum@ and @Value@ predicates.

instance Haskell.Show TxConstraintFun where
    showsPrec :: Int -> TxConstraintFun -> ShowS
showsPrec Int
_ = SimpleDocStream Any -> ShowS
forall ann. SimpleDocStream ann -> ShowS
renderShowS (SimpleDocStream Any -> ShowS)
-> (TxConstraintFun -> SimpleDocStream Any)
-> TxConstraintFun
-> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LayoutOptions -> Doc Any -> SimpleDocStream Any
forall ann. LayoutOptions -> Doc ann -> SimpleDocStream ann
layoutPretty LayoutOptions
defaultLayoutOptions (Doc Any -> SimpleDocStream Any)
-> (TxConstraintFun -> Doc Any)
-> TxConstraintFun
-> SimpleDocStream Any
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxConstraintFun -> Doc Any
forall a ann. Pretty a => a -> Doc ann
pretty

instance Pretty TxConstraintFun where
    pretty :: TxConstraintFun -> Doc ann
pretty = \case
        MustSpendScriptOutputWithMatchingDatumAndValue ValidatorHash
sh Datum -> Bool
_ Value -> Bool
_ Redeemer
red ->
            Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
hang Int
2 (Doc ann -> Doc ann) -> Doc ann -> Doc ann
forall a b. (a -> b) -> a -> b
$ [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"must spend script out from script hash: ", ValidatorHash -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ValidatorHash
sh, Redeemer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Redeemer
red]

newtype TxConstraintFuns = TxConstraintFuns [TxConstraintFun]
    deriving stock (Int -> TxConstraintFuns -> ShowS
[TxConstraintFuns] -> ShowS
TxConstraintFuns -> String
(Int -> TxConstraintFuns -> ShowS)
-> (TxConstraintFuns -> String)
-> ([TxConstraintFuns] -> ShowS)
-> Show TxConstraintFuns
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TxConstraintFuns] -> ShowS
$cshowList :: [TxConstraintFuns] -> ShowS
show :: TxConstraintFuns -> String
$cshow :: TxConstraintFuns -> String
showsPrec :: Int -> TxConstraintFuns -> ShowS
$cshowsPrec :: Int -> TxConstraintFuns -> ShowS
Haskell.Show, (forall x. TxConstraintFuns -> Rep TxConstraintFuns x)
-> (forall x. Rep TxConstraintFuns x -> TxConstraintFuns)
-> Generic TxConstraintFuns
forall x. Rep TxConstraintFuns x -> TxConstraintFuns
forall x. TxConstraintFuns -> Rep TxConstraintFuns x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep TxConstraintFuns x -> TxConstraintFuns
$cfrom :: forall x. TxConstraintFuns -> Rep TxConstraintFuns x
Generic)
    deriving newtype (TxConstraintFuns -> TxConstraintFuns -> TxConstraintFuns
(TxConstraintFuns -> TxConstraintFuns -> TxConstraintFuns)
-> Semigroup TxConstraintFuns
forall a. (a -> a -> a) -> Semigroup a
<> :: TxConstraintFuns -> TxConstraintFuns -> TxConstraintFuns
$c<> :: TxConstraintFuns -> TxConstraintFuns -> TxConstraintFuns
Semigroup, Semigroup TxConstraintFuns
TxConstraintFuns
Semigroup TxConstraintFuns
-> TxConstraintFuns -> Monoid TxConstraintFuns
forall a. Semigroup a -> a -> Monoid a
mempty :: TxConstraintFuns
$cmempty :: TxConstraintFuns
$cp1Monoid :: Semigroup TxConstraintFuns
Monoid)

-- We can't convert functons to JSON, so we have a @TxConstraintFuns@ wrapper to provide dummy To/FromJSON instances.
instance ToJSON TxConstraintFuns where
    toJSON :: TxConstraintFuns -> Value
toJSON TxConstraintFuns
_ = Array -> Value
Aeson.Array Array
forall a. Monoid a => a
Haskell.mempty

instance FromJSON TxConstraintFuns where
    parseJSON :: Value -> Parser TxConstraintFuns
parseJSON Value
_ = TxConstraintFuns -> Parser TxConstraintFuns
forall (f :: * -> *) a. Applicative f => a -> f a
Haskell.pure TxConstraintFuns
forall a. Monoid a => a
mempty

-- | Constraint which specifies that the transaction must spend a transaction
-- output from a target script.
data ScriptInputConstraint a =
    ScriptInputConstraint
        { ScriptInputConstraint a -> a
icRedeemer          :: a -- ^ The typed 'Redeemer' to be used with the target script
        , ScriptInputConstraint a -> TxOutRef
icTxOutRef          :: TxOutRef -- ^ The UTXO to be spent by the target script
        , ScriptInputConstraint a -> Maybe TxOutRef
icReferenceTxOutRef :: Maybe TxOutRef -- ^ Optionally use a reference script as witness
        } deriving stock (Int -> ScriptInputConstraint a -> ShowS
[ScriptInputConstraint a] -> ShowS
ScriptInputConstraint a -> String
(Int -> ScriptInputConstraint a -> ShowS)
-> (ScriptInputConstraint a -> String)
-> ([ScriptInputConstraint a] -> ShowS)
-> Show (ScriptInputConstraint a)
forall a. Show a => Int -> ScriptInputConstraint a -> ShowS
forall a. Show a => [ScriptInputConstraint a] -> ShowS
forall a. Show a => ScriptInputConstraint a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScriptInputConstraint a] -> ShowS
$cshowList :: forall a. Show a => [ScriptInputConstraint a] -> ShowS
show :: ScriptInputConstraint a -> String
$cshow :: forall a. Show a => ScriptInputConstraint a -> String
showsPrec :: Int -> ScriptInputConstraint a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ScriptInputConstraint a -> ShowS
Haskell.Show, (forall x.
 ScriptInputConstraint a -> Rep (ScriptInputConstraint a) x)
-> (forall x.
    Rep (ScriptInputConstraint a) x -> ScriptInputConstraint a)
-> Generic (ScriptInputConstraint a)
forall x.
Rep (ScriptInputConstraint a) x -> ScriptInputConstraint a
forall x.
ScriptInputConstraint a -> Rep (ScriptInputConstraint a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x.
Rep (ScriptInputConstraint a) x -> ScriptInputConstraint a
forall a x.
ScriptInputConstraint a -> Rep (ScriptInputConstraint a) x
$cto :: forall a x.
Rep (ScriptInputConstraint a) x -> ScriptInputConstraint a
$cfrom :: forall a x.
ScriptInputConstraint a -> Rep (ScriptInputConstraint a) x
Generic, a -> ScriptInputConstraint b -> ScriptInputConstraint a
(a -> b) -> ScriptInputConstraint a -> ScriptInputConstraint b
(forall a b.
 (a -> b) -> ScriptInputConstraint a -> ScriptInputConstraint b)
-> (forall a b.
    a -> ScriptInputConstraint b -> ScriptInputConstraint a)
-> Functor ScriptInputConstraint
forall a b. a -> ScriptInputConstraint b -> ScriptInputConstraint a
forall a b.
(a -> b) -> ScriptInputConstraint a -> ScriptInputConstraint b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> ScriptInputConstraint b -> ScriptInputConstraint a
$c<$ :: forall a b. a -> ScriptInputConstraint b -> ScriptInputConstraint a
fmap :: (a -> b) -> ScriptInputConstraint a -> ScriptInputConstraint b
$cfmap :: forall a b.
(a -> b) -> ScriptInputConstraint a -> ScriptInputConstraint b
Haskell.Functor)

{-# INLINABLE mustSpendOutputFromTheScript #-}
-- | @mustSpendOutputFromTheScript txOutRef red@ spends the transaction output
-- @txOutRef@ with a script address using the redeemer @red@.
--
-- If used in 'Ledger.Constraints.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 'Ledger.Constraints.OffChain.ScriptLookups' with
-- 'Ledger.Constraints.OffChain.typedValidatorLookups'.
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies that the
-- spend script transaction output with @red@ is part of the transaction's
-- inputs.
mustSpendOutputFromTheScript :: TxOutRef -> i -> TxConstraints i o
mustSpendOutputFromTheScript :: TxOutRef -> i -> TxConstraints i o
mustSpendOutputFromTheScript TxOutRef
txOutRef i
red =
    TxConstraints Any o
forall a. Monoid a => a
mempty { txOwnInputs :: [ScriptInputConstraint i]
txOwnInputs = [i -> TxOutRef -> Maybe TxOutRef -> ScriptInputConstraint i
forall a.
a -> TxOutRef -> Maybe TxOutRef -> ScriptInputConstraint a
ScriptInputConstraint i
red TxOutRef
txOutRef Maybe TxOutRef
forall a. Maybe a
Nothing] }

instance (Pretty a) => Pretty (ScriptInputConstraint a) where
    pretty :: ScriptInputConstraint a -> Doc ann
pretty ScriptInputConstraint{a
icRedeemer :: a
icRedeemer :: forall a. ScriptInputConstraint a -> a
icRedeemer, TxOutRef
icTxOutRef :: TxOutRef
icTxOutRef :: forall a. ScriptInputConstraint a -> TxOutRef
icTxOutRef, Maybe TxOutRef
icReferenceTxOutRef :: Maybe TxOutRef
icReferenceTxOutRef :: forall a. ScriptInputConstraint a -> Maybe TxOutRef
icReferenceTxOutRef} =
        [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$
            [ Doc ann
"Redeemer:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> a -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty a
icRedeemer
            , Doc ann
"TxOutRef:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOutRef
icTxOutRef
            ] [Doc ann] -> [Doc ann] -> [Doc ann]
forall a. [a] -> [a] -> [a]
Haskell.++ [Doc ann] -> (TxOutRef -> [Doc ann]) -> Maybe TxOutRef -> [Doc ann]
forall b a. b -> (a -> b) -> Maybe a -> b
Haskell.maybe [] (\TxOutRef
ref -> [Doc ann
"Reference TxOutRef: " Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOutRef
ref]) Maybe TxOutRef
icReferenceTxOutRef

deriving anyclass instance (ToJSON a) => ToJSON (ScriptInputConstraint a)
deriving anyclass instance (FromJSON a) => FromJSON (ScriptInputConstraint a)
deriving stock instance (Haskell.Eq a) => Haskell.Eq (ScriptInputConstraint a)

-- Constraint which specifies that the transaction must produce a transaction
-- output which pays to a target script.
data ScriptOutputConstraint a =
    ScriptOutputConstraint
        { ScriptOutputConstraint a -> TxOutDatum a
ocDatum               :: TxOutDatum a -- ^ Typed datum to be used with the target script
        , ScriptOutputConstraint a -> Value
ocValue               :: Value
        , ScriptOutputConstraint a -> Maybe ScriptHash
ocReferenceScriptHash :: Maybe ScriptHash
        } deriving stock (Int -> ScriptOutputConstraint a -> ShowS
[ScriptOutputConstraint a] -> ShowS
ScriptOutputConstraint a -> String
(Int -> ScriptOutputConstraint a -> ShowS)
-> (ScriptOutputConstraint a -> String)
-> ([ScriptOutputConstraint a] -> ShowS)
-> Show (ScriptOutputConstraint a)
forall a. Show a => Int -> ScriptOutputConstraint a -> ShowS
forall a. Show a => [ScriptOutputConstraint a] -> ShowS
forall a. Show a => ScriptOutputConstraint a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ScriptOutputConstraint a] -> ShowS
$cshowList :: forall a. Show a => [ScriptOutputConstraint a] -> ShowS
show :: ScriptOutputConstraint a -> String
$cshow :: forall a. Show a => ScriptOutputConstraint a -> String
showsPrec :: Int -> ScriptOutputConstraint a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> ScriptOutputConstraint a -> ShowS
Haskell.Show, (forall x.
 ScriptOutputConstraint a -> Rep (ScriptOutputConstraint a) x)
-> (forall x.
    Rep (ScriptOutputConstraint a) x -> ScriptOutputConstraint a)
-> Generic (ScriptOutputConstraint a)
forall x.
Rep (ScriptOutputConstraint a) x -> ScriptOutputConstraint a
forall x.
ScriptOutputConstraint a -> Rep (ScriptOutputConstraint a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x.
Rep (ScriptOutputConstraint a) x -> ScriptOutputConstraint a
forall a x.
ScriptOutputConstraint a -> Rep (ScriptOutputConstraint a) x
$cto :: forall a x.
Rep (ScriptOutputConstraint a) x -> ScriptOutputConstraint a
$cfrom :: forall a x.
ScriptOutputConstraint a -> Rep (ScriptOutputConstraint a) x
Generic, a -> ScriptOutputConstraint b -> ScriptOutputConstraint a
(a -> b) -> ScriptOutputConstraint a -> ScriptOutputConstraint b
(forall a b.
 (a -> b) -> ScriptOutputConstraint a -> ScriptOutputConstraint b)
-> (forall a b.
    a -> ScriptOutputConstraint b -> ScriptOutputConstraint a)
-> Functor ScriptOutputConstraint
forall a b.
a -> ScriptOutputConstraint b -> ScriptOutputConstraint a
forall a b.
(a -> b) -> ScriptOutputConstraint a -> ScriptOutputConstraint b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> ScriptOutputConstraint b -> ScriptOutputConstraint a
$c<$ :: forall a b.
a -> ScriptOutputConstraint b -> ScriptOutputConstraint a
fmap :: (a -> b) -> ScriptOutputConstraint a -> ScriptOutputConstraint b
$cfmap :: forall a b.
(a -> b) -> ScriptOutputConstraint a -> ScriptOutputConstraint b
Haskell.Functor)

instance (Pretty a) => Pretty (ScriptOutputConstraint a) where
    pretty :: ScriptOutputConstraint a -> Doc ann
pretty ScriptOutputConstraint{TxOutDatum a
ocDatum :: TxOutDatum a
ocDatum :: forall a. ScriptOutputConstraint a -> TxOutDatum a
ocDatum, Value
ocValue :: Value
ocValue :: forall a. ScriptOutputConstraint a -> Value
ocValue, Maybe ScriptHash
ocReferenceScriptHash :: Maybe ScriptHash
ocReferenceScriptHash :: forall a. ScriptOutputConstraint a -> Maybe ScriptHash
ocReferenceScriptHash} =
        [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep ([Doc ann] -> Doc ann) -> [Doc ann] -> Doc ann
forall a b. (a -> b) -> a -> b
$
            [ Doc ann
"Datum:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxOutDatum a -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOutDatum a
ocDatum
            , Doc ann
"Value:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Value
ocValue
            ] [Doc ann] -> [Doc ann] -> [Doc ann]
forall a. [a] -> [a] -> [a]
Haskell.++ [Doc ann]
-> (ScriptHash -> [Doc ann]) -> Maybe ScriptHash -> [Doc ann]
forall b a. b -> (a -> b) -> Maybe a -> b
Haskell.maybe [] (\ScriptHash
sh -> [Doc ann
"Reference script hash: " Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> ScriptHash -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ScriptHash
sh]) Maybe ScriptHash
ocReferenceScriptHash

deriving anyclass instance (ToJSON a) => ToJSON (ScriptOutputConstraint a)
deriving anyclass instance (FromJSON a) => FromJSON (ScriptOutputConstraint a)
deriving stock instance (Haskell.Eq a) => Haskell.Eq (ScriptOutputConstraint a)

-- | Restrictions placed on the allocation of funds to outputs of transactions.
data TxConstraints i o =
    TxConstraints
        { TxConstraints i o -> [TxConstraint]
txConstraints    :: [TxConstraint]
        , TxConstraints i o -> TxConstraintFuns
txConstraintFuns :: TxConstraintFuns
        , TxConstraints i o -> [ScriptInputConstraint i]
txOwnInputs      :: [ScriptInputConstraint i]
        , TxConstraints i o -> [ScriptOutputConstraint o]
txOwnOutputs     :: [ScriptOutputConstraint o]
        }
    deriving stock (Int -> TxConstraints i o -> ShowS
[TxConstraints i o] -> ShowS
TxConstraints i o -> String
(Int -> TxConstraints i o -> ShowS)
-> (TxConstraints i o -> String)
-> ([TxConstraints i o] -> ShowS)
-> Show (TxConstraints i o)
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall i o. (Show i, Show o) => Int -> TxConstraints i o -> ShowS
forall i o. (Show i, Show o) => [TxConstraints i o] -> ShowS
forall i o. (Show i, Show o) => TxConstraints i o -> String
showList :: [TxConstraints i o] -> ShowS
$cshowList :: forall i o. (Show i, Show o) => [TxConstraints i o] -> ShowS
show :: TxConstraints i o -> String
$cshow :: forall i o. (Show i, Show o) => TxConstraints i o -> String
showsPrec :: Int -> TxConstraints i o -> ShowS
$cshowsPrec :: forall i o. (Show i, Show o) => Int -> TxConstraints i o -> ShowS
Haskell.Show, (forall x. TxConstraints i o -> Rep (TxConstraints i o) x)
-> (forall x. Rep (TxConstraints i o) x -> TxConstraints i o)
-> Generic (TxConstraints i o)
forall x. Rep (TxConstraints i o) x -> TxConstraints i o
forall x. TxConstraints i o -> Rep (TxConstraints i o) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall i o x. Rep (TxConstraints i o) x -> TxConstraints i o
forall i o x. TxConstraints i o -> Rep (TxConstraints i o) x
$cto :: forall i o x. Rep (TxConstraints i o) x -> TxConstraints i o
$cfrom :: forall i o x. TxConstraints i o -> Rep (TxConstraints i o) x
Generic)

instance Bifunctor TxConstraints where
    bimap :: (a -> b) -> (c -> d) -> TxConstraints a c -> TxConstraints b d
bimap a -> b
f c -> d
g TxConstraints a c
txc =
        TxConstraints a c
txc
            { txOwnInputs :: [ScriptInputConstraint b]
txOwnInputs = (ScriptInputConstraint a -> ScriptInputConstraint b)
-> [ScriptInputConstraint a] -> [ScriptInputConstraint b]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Haskell.fmap ((a -> b) -> ScriptInputConstraint a -> ScriptInputConstraint b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Haskell.fmap a -> b
f) (TxConstraints a c -> [ScriptInputConstraint a]
forall i o. TxConstraints i o -> [ScriptInputConstraint i]
txOwnInputs TxConstraints a c
txc)
            , txOwnOutputs :: [ScriptOutputConstraint d]
txOwnOutputs = (ScriptOutputConstraint c -> ScriptOutputConstraint d)
-> [ScriptOutputConstraint c] -> [ScriptOutputConstraint d]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Haskell.fmap ((c -> d) -> ScriptOutputConstraint c -> ScriptOutputConstraint d
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Haskell.fmap c -> d
g) (TxConstraints a c -> [ScriptOutputConstraint c]
forall i o. TxConstraints i o -> [ScriptOutputConstraint o]
txOwnOutputs TxConstraints a c
txc)
            }

type UntypedConstraints = TxConstraints PlutusTx.BuiltinData PlutusTx.BuiltinData

instance Semigroup (TxConstraints i o) where
    TxConstraints i o
l <> :: TxConstraints i o -> TxConstraints i o -> TxConstraints i o
<> TxConstraints i o
r =
        TxConstraints :: forall i o.
[TxConstraint]
-> TxConstraintFuns
-> [ScriptInputConstraint i]
-> [ScriptOutputConstraint o]
-> TxConstraints i o
TxConstraints
            { txConstraints :: [TxConstraint]
txConstraints = TxConstraints i o -> [TxConstraint]
forall i o. TxConstraints i o -> [TxConstraint]
txConstraints TxConstraints i o
l [TxConstraint] -> [TxConstraint] -> [TxConstraint]
forall a. Semigroup a => a -> a -> a
<> TxConstraints i o -> [TxConstraint]
forall i o. TxConstraints i o -> [TxConstraint]
txConstraints TxConstraints i o
r
            , txConstraintFuns :: TxConstraintFuns
txConstraintFuns = TxConstraints i o -> TxConstraintFuns
forall i o. TxConstraints i o -> TxConstraintFuns
txConstraintFuns TxConstraints i o
l TxConstraintFuns -> TxConstraintFuns -> TxConstraintFuns
forall a. Semigroup a => a -> a -> a
<> TxConstraints i o -> TxConstraintFuns
forall i o. TxConstraints i o -> TxConstraintFuns
txConstraintFuns TxConstraints i o
r
            , txOwnInputs :: [ScriptInputConstraint i]
txOwnInputs = TxConstraints i o -> [ScriptInputConstraint i]
forall i o. TxConstraints i o -> [ScriptInputConstraint i]
txOwnInputs TxConstraints i o
l [ScriptInputConstraint i]
-> [ScriptInputConstraint i] -> [ScriptInputConstraint i]
forall a. Semigroup a => a -> a -> a
<> TxConstraints i o -> [ScriptInputConstraint i]
forall i o. TxConstraints i o -> [ScriptInputConstraint i]
txOwnInputs TxConstraints i o
r
            , txOwnOutputs :: [ScriptOutputConstraint o]
txOwnOutputs = TxConstraints i o -> [ScriptOutputConstraint o]
forall i o. TxConstraints i o -> [ScriptOutputConstraint o]
txOwnOutputs TxConstraints i o
l [ScriptOutputConstraint o]
-> [ScriptOutputConstraint o] -> [ScriptOutputConstraint o]
forall a. Semigroup a => a -> a -> a
<> TxConstraints i o -> [ScriptOutputConstraint o]
forall i o. TxConstraints i o -> [ScriptOutputConstraint o]
txOwnOutputs TxConstraints i o
r
            }

instance Haskell.Semigroup (TxConstraints i o) where
    <> :: TxConstraints i o -> TxConstraints i o -> TxConstraints i o
(<>) = TxConstraints i o -> TxConstraints i o -> TxConstraints i o
forall a. Semigroup a => a -> a -> a
(<>) -- uses PlutusTx.Semigroup instance

instance Monoid (TxConstraints i o) where
    mempty :: TxConstraints i o
mempty = [TxConstraint]
-> TxConstraintFuns
-> [ScriptInputConstraint i]
-> [ScriptOutputConstraint o]
-> TxConstraints i o
forall i o.
[TxConstraint]
-> TxConstraintFuns
-> [ScriptInputConstraint i]
-> [ScriptOutputConstraint o]
-> TxConstraints i o
TxConstraints [TxConstraint]
forall a. Monoid a => a
mempty TxConstraintFuns
forall a. Monoid a => a
mempty [ScriptInputConstraint i]
forall a. Monoid a => a
mempty [ScriptOutputConstraint o]
forall a. Monoid a => a
mempty

instance Haskell.Monoid (TxConstraints i o) where
    mappend :: TxConstraints i o -> TxConstraints i o -> TxConstraints i o
mappend = TxConstraints i o -> TxConstraints i o -> TxConstraints i o
forall a. Semigroup a => a -> a -> a
(<>)
    mempty :: TxConstraints i o
mempty  = TxConstraints i o
forall a. Monoid a => a
mempty

deriving anyclass instance (ToJSON i, ToJSON o) => ToJSON (TxConstraints i o)
deriving anyclass instance (FromJSON i, FromJSON o) => FromJSON (TxConstraints i o)
-- deriving stock instance (Haskell.Eq i, Haskell.Eq o) => Haskell.Eq (TxConstraints i o)

{-# INLINABLE singleton #-}
singleton :: TxConstraint -> TxConstraints i o
singleton :: TxConstraint -> TxConstraints i o
singleton TxConstraint
a = TxConstraints i o
forall a. Monoid a => a
mempty { txConstraints :: [TxConstraint]
txConstraints = [TxConstraint
a] }

{-# INLINABLE mustValidateIn #-}
{-# DEPRECATED mustValidateIn "Please use mustValidateInTimeRange or mustValidateInSlotRange instead" #-}
-- | @mustValidateIn r@ requires the transaction's validity time range to be contained
--   in POSIXTimeRange @r@.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint sets the
-- transaction's validity time range to @r@.
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies that the
-- time range @r@ is entirely contained in the transaction's validity time range.
mustValidateIn :: forall i o. POSIXTimeRange -> TxConstraints i o
mustValidateIn :: POSIXTimeRange -> TxConstraints i o
mustValidateIn = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> (POSIXTimeRange -> TxConstraint)
-> POSIXTimeRange
-> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValidityInterval POSIXTime -> TxConstraint
MustValidateInTimeRange (ValidityInterval POSIXTime -> TxConstraint)
-> (POSIXTimeRange -> ValidityInterval POSIXTime)
-> POSIXTimeRange
-> TxConstraint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. POSIXTimeRange -> ValidityInterval POSIXTime
forall a. Enum a => Interval a -> ValidityInterval a
fromPlutusInterval

{-# INLINABLE mustValidateInTimeRange #-}
-- | @mustValidateInTimeRange r@ requires the transaction's validity time range to be contained
--   in POSIXTime range @r@.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint sets the
-- transaction's validity time range to @r@.
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies that the
-- time range @r@ is entirely contained in the transaction's validity time range.
mustValidateInTimeRange :: forall i o. ValidityInterval POSIXTime -> TxConstraints i o
mustValidateInTimeRange :: ValidityInterval POSIXTime -> TxConstraints i o
mustValidateInTimeRange = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> (ValidityInterval POSIXTime -> TxConstraint)
-> ValidityInterval POSIXTime
-> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValidityInterval POSIXTime -> TxConstraint
MustValidateInTimeRange

{-# INLINABLE mustValidateInSlotRange #-}
-- | @mustValidateInSlotRange r@ requires the transaction's validity slot range to be contained
--   in Slot range @r@.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint sets the
-- transaction's validity slot range to @r@.
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies that the
-- slot range @r@ is entirely contained in the transaction's validity time range.
mustValidateInSlotRange :: forall i o. ValidityInterval Slot -> TxConstraints i o
mustValidateInSlotRange :: ValidityInterval Slot -> TxConstraints i o
mustValidateInSlotRange = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> (ValidityInterval Slot -> TxConstraint)
-> ValidityInterval Slot
-> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValidityInterval POSIXTime -> TxConstraint
MustValidateInTimeRange (ValidityInterval POSIXTime -> TxConstraint)
-> (ValidityInterval Slot -> ValidityInterval POSIXTime)
-> ValidityInterval Slot
-> TxConstraint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. POSIXTimeRange -> ValidityInterval POSIXTime
forall a. Enum a => Interval a -> ValidityInterval a
fromPlutusInterval (POSIXTimeRange -> ValidityInterval POSIXTime)
-> (ValidityInterval Slot -> POSIXTimeRange)
-> ValidityInterval Slot
-> ValidityInterval POSIXTime
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SlotConfig -> SlotRange -> POSIXTimeRange
slotRangeToPOSIXTimeRange SlotConfig
forall a. Default a => a
def (SlotRange -> POSIXTimeRange)
-> (ValidityInterval Slot -> SlotRange)
-> ValidityInterval Slot
-> POSIXTimeRange
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ValidityInterval Slot -> SlotRange
forall a. ValidityInterval a -> Interval a
toPlutusInterval

{-# INLINABLE mustBeSignedBy #-}
-- | @mustBeSignedBy pk@ requires the transaction to be signed by the public
-- key @pk@.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint adds @pk@ in the
-- transaction's public key witness set.
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies that @pk@
-- is part of the transaction's public key witness set.
mustBeSignedBy :: forall i o. PaymentPubKeyHash -> TxConstraints i o
mustBeSignedBy :: PaymentPubKeyHash -> TxConstraints i o
mustBeSignedBy = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> (PaymentPubKeyHash -> TxConstraint)
-> PaymentPubKeyHash
-> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. PaymentPubKeyHash -> TxConstraint
MustBeSignedBy

{-# INLINABLE mustIncludeDatumInTxWithHash #-}
-- | @mustIncludeDatumInTxWithHash dh d@ requires the transaction body to
-- include the datum hash @dh@ and actual datum @d@.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint adds @dh@ and @d@
-- in the transaction's body.
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies that @dh@
-- and @d@ are part of the transaction's body.
mustIncludeDatumInTxWithHash :: DatumHash -> Datum -> TxConstraints i o
mustIncludeDatumInTxWithHash :: DatumHash -> Datum -> TxConstraints i o
mustIncludeDatumInTxWithHash DatumHash
dvh = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> (Datum -> TxConstraint) -> Datum -> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. DatumHash -> Datum -> TxConstraint
MustIncludeDatumInTxWithHash DatumHash
dvh

{-# INLINABLE mustIncludeDatumInTx #-}
-- | @mustIncludeDatumInTx d@ requires the transaction body to include the
-- datum @d@.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint adds @d@ in the
-- transaction's body alongside it's hash (which is computed automatically).
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies that @d@
-- is part of the transaction's body.
mustIncludeDatumInTx :: forall i o. Datum -> TxConstraints i o
mustIncludeDatumInTx :: Datum -> TxConstraints i o
mustIncludeDatumInTx = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> (Datum -> TxConstraint) -> Datum -> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Datum -> TxConstraint
MustIncludeDatumInTx

{-# DEPRECATED mustPayToTheScript "Use mustPayToTheScriptWithDatumHash instead" #-}
mustPayToTheScript :: o -> Value -> TxConstraints i o
mustPayToTheScript :: o -> Value -> TxConstraints i o
mustPayToTheScript = o -> Value -> TxConstraints i o
forall o i. o -> Value -> TxConstraints i o
mustPayToTheScriptWithDatumHash

{-# INLINABLE mustPayToTheScriptWithDatumHash #-}
-- | @mustPayToTheScriptWithDatumHash d v@ locks the value @v@ with a script alongside a
-- datum @d@ which is included in the transaction body.
--
-- If used in 'Ledger.Constraints.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 'Ledger.Constraints.OffChain.ScriptLookups' with
-- 'Ledger.Constraints.OffChain.typedValidatorLookups'.
--
-- If used in 'Ledger.Constraints.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.
mustPayToTheScriptWithDatumHash :: o -> Value -> TxConstraints i o
mustPayToTheScriptWithDatumHash :: o -> Value -> TxConstraints i o
mustPayToTheScriptWithDatumHash o
dt Value
vl =
    TxConstraints i Any
forall a. Monoid a => a
mempty { txOwnOutputs :: [ScriptOutputConstraint o]
txOwnOutputs = [TxOutDatum o
-> Value -> Maybe ScriptHash -> ScriptOutputConstraint o
forall a.
TxOutDatum a
-> Value -> Maybe ScriptHash -> ScriptOutputConstraint a
ScriptOutputConstraint (o -> TxOutDatum o
forall datum. datum -> TxOutDatum datum
TxOutDatumHash o
dt) Value
vl Maybe ScriptHash
forall a. Maybe a
Nothing] }

{-# INLINABLE mustPayToTheScriptWithDatumInTx #-}
mustPayToTheScriptWithDatumInTx :: o -> Value -> TxConstraints i o
mustPayToTheScriptWithDatumInTx :: o -> Value -> TxConstraints i o
mustPayToTheScriptWithDatumInTx o
dt Value
vl =
    TxConstraints i Any
forall a. Monoid a => a
mempty { txOwnOutputs :: [ScriptOutputConstraint o]
txOwnOutputs = [TxOutDatum o
-> Value -> Maybe ScriptHash -> ScriptOutputConstraint o
forall a.
TxOutDatum a
-> Value -> Maybe ScriptHash -> ScriptOutputConstraint a
ScriptOutputConstraint (o -> TxOutDatum o
forall datum. datum -> TxOutDatum datum
TxOutDatumInTx o
dt) Value
vl Maybe ScriptHash
forall a. Maybe a
Nothing] }

{-# INLINABLE mustPayToTheScriptWithInlineDatum #-}
mustPayToTheScriptWithInlineDatum :: o -> Value -> TxConstraints i o
mustPayToTheScriptWithInlineDatum :: o -> Value -> TxConstraints i o
mustPayToTheScriptWithInlineDatum o
dt Value
vl =
    TxConstraints i Any
forall a. Monoid a => a
mempty { txOwnOutputs :: [ScriptOutputConstraint o]
txOwnOutputs = [TxOutDatum o
-> Value -> Maybe ScriptHash -> ScriptOutputConstraint o
forall a.
TxOutDatum a
-> Value -> Maybe ScriptHash -> ScriptOutputConstraint a
ScriptOutputConstraint (o -> TxOutDatum o
forall datum. datum -> TxOutDatum datum
TxOutDatumInline o
dt) Value
vl Maybe ScriptHash
forall a. Maybe a
Nothing] }

{-# INLINABLE mustPayToTheScriptWithReferenceScript #-}
mustPayToTheScriptWithReferenceScript :: ScriptHash -> TxOutDatum o -> Value -> TxConstraints i o
mustPayToTheScriptWithReferenceScript :: ScriptHash -> TxOutDatum o -> Value -> TxConstraints i o
mustPayToTheScriptWithReferenceScript ScriptHash
sh TxOutDatum o
dt Value
vl =
    TxConstraints i Any
forall a. Monoid a => a
mempty { txOwnOutputs :: [ScriptOutputConstraint o]
txOwnOutputs = [TxOutDatum o
-> Value -> Maybe ScriptHash -> ScriptOutputConstraint o
forall a.
TxOutDatum a
-> Value -> Maybe ScriptHash -> ScriptOutputConstraint a
ScriptOutputConstraint TxOutDatum o
dt Value
vl (ScriptHash -> Maybe ScriptHash
forall a. a -> Maybe a
Just ScriptHash
sh)] }

{-# INLINABLE mustPayToPubKey #-}
-- | @mustPayToPubKey pkh v@ is the same as
-- 'mustPayToPubKeyAddressWithDatumHash', but without any staking key hash and datum.
mustPayToPubKey :: forall i o. PaymentPubKeyHash -> Value -> TxConstraints i o
mustPayToPubKey :: PaymentPubKeyHash -> Value -> TxConstraints i o
mustPayToPubKey (PaymentPubKeyHash PubKeyHash
pkh) Value
vl = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (PubKeyHash -> Credential
PubKeyCredential PubKeyHash
pkh) Maybe StakingCredential
forall a. Maybe a
Nothing) Maybe (TxOutDatum Datum)
forall a. Maybe a
Nothing Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# INLINABLE mustPayToPubKeyAddress #-}
-- | @mustPayToPubKeyAddress pkh skh v@ is the same as
-- 'mustPayToPubKeyAddressWithDatumHash', but without any datum.
mustPayToPubKeyAddress
    :: forall i o
     . PaymentPubKeyHash
    -> StakingCredential
    -> Value
    -> TxConstraints i o
mustPayToPubKeyAddress :: PaymentPubKeyHash
-> StakingCredential -> Value -> TxConstraints i o
mustPayToPubKeyAddress (PaymentPubKeyHash PubKeyHash
pkh) StakingCredential
sc Value
vl =
     TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (PubKeyHash -> Credential
PubKeyCredential PubKeyHash
pkh) (StakingCredential -> Maybe StakingCredential
forall a. a -> Maybe a
Just StakingCredential
sc)) Maybe (TxOutDatum Datum)
forall a. Maybe a
Nothing Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# DEPRECATED mustPayWithDatumToPubKey "Use mustPayToPubKeyWithDatumHash instead" #-}
mustPayWithDatumToPubKey
    :: forall i o
     . PaymentPubKeyHash
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayWithDatumToPubKey :: PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
mustPayWithDatumToPubKey = PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
forall i o.
PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
mustPayToPubKeyWithDatumHash

{-# INLINABLE mustPayToPubKeyWithDatumHash #-}
-- | @mustPayToPubKeyWithDatumHash pkh d v@ is the same as
-- 'mustPayToPubKeyAddressWithDatumHash', but without the staking key hash.
mustPayToPubKeyWithDatumHash
    :: forall i o
     . PaymentPubKeyHash
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayToPubKeyWithDatumHash :: PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
mustPayToPubKeyWithDatumHash (PaymentPubKeyHash PubKeyHash
pkh) Datum
datum Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (PubKeyHash -> Credential
PubKeyCredential PubKeyHash
pkh) Maybe StakingCredential
forall a. Maybe a
Nothing) (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (TxOutDatum Datum -> Maybe (TxOutDatum Datum))
-> TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a b. (a -> b) -> a -> b
$ Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumHash Datum
datum) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# DEPRECATED mustPayWithDatumInTxToPubKey "Use mustPayToPubKeyWithDatumInTx instead" #-}
mustPayWithDatumInTxToPubKey
    :: forall i o
     . PaymentPubKeyHash
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayWithDatumInTxToPubKey :: PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
mustPayWithDatumInTxToPubKey = PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
forall i o.
PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
mustPayToPubKeyWithDatumInTx

{-# INLINABLE mustPayToPubKeyWithDatumInTx #-}
-- | @mustPayToPubKeyWithDatumInTx pkh d v@ is the same as
-- 'mustPayToPubKeyAddressWithDatumHash', but with an inline datum and without the staking key hash.
mustPayToPubKeyWithDatumInTx
    :: forall i o
     . PaymentPubKeyHash
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayToPubKeyWithDatumInTx :: PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
mustPayToPubKeyWithDatumInTx (PaymentPubKeyHash PubKeyHash
pkh) Datum
datum Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (PubKeyHash -> Credential
PubKeyCredential PubKeyHash
pkh) Maybe StakingCredential
forall a. Maybe a
Nothing) (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (TxOutDatum Datum -> Maybe (TxOutDatum Datum))
-> TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a b. (a -> b) -> a -> b
$ Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumInTx Datum
datum) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# DEPRECATED mustPayWithInlineDatumToPubKey "Use mustPayToPubKeyWithInlineDatum instead" #-}
mustPayWithInlineDatumToPubKey
    :: forall i o
     . PaymentPubKeyHash
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayWithInlineDatumToPubKey :: PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
mustPayWithInlineDatumToPubKey = PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
forall i o.
PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
mustPayToPubKeyWithInlineDatum

{-# INLINABLE mustPayToPubKeyWithInlineDatum #-}
-- | @mustPayToPubKeyWithInlineDatum pkh d v@ is the same as
-- 'mustPayToPubKeyAddressWithDatumHash', but with an inline datum and without the staking key hash.
mustPayToPubKeyWithInlineDatum
    :: forall i o
     . PaymentPubKeyHash
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayToPubKeyWithInlineDatum :: PaymentPubKeyHash -> Datum -> Value -> TxConstraints i o
mustPayToPubKeyWithInlineDatum (PaymentPubKeyHash PubKeyHash
pkh) Datum
datum Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (PubKeyHash -> Credential
PubKeyCredential PubKeyHash
pkh) Maybe StakingCredential
forall a. Maybe a
Nothing) (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (TxOutDatum Datum -> Maybe (TxOutDatum Datum))
-> TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a b. (a -> b) -> a -> b
$ Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumInline Datum
datum) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# DEPRECATED mustPayWithDatumToPubKeyAddress "Use mustPayToPubKeyAddressWithDatumHash instead" #-}
mustPayWithDatumToPubKeyAddress
    :: forall i o
     . PaymentPubKeyHash
    -> StakingCredential
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayWithDatumToPubKeyAddress :: PaymentPubKeyHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayWithDatumToPubKeyAddress = PaymentPubKeyHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
forall i o.
PaymentPubKeyHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToPubKeyAddressWithDatumHash

{-# INLINABLE mustPayToPubKeyAddressWithDatumHash #-}
-- | @mustPayToPubKeyAddressWithDatumHash pkh skh d v@ locks a transaction output
-- with a public key address.
--
-- If used in 'Ledger.Constraints.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 'Ledger.Constraints.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.
mustPayToPubKeyAddressWithDatumHash
    :: forall i o
     . PaymentPubKeyHash
    -> StakingCredential
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayToPubKeyAddressWithDatumHash :: PaymentPubKeyHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToPubKeyAddressWithDatumHash (PaymentPubKeyHash PubKeyHash
pkh) StakingCredential
sc Datum
datum Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (PubKeyHash -> Credential
PubKeyCredential PubKeyHash
pkh) (StakingCredential -> Maybe StakingCredential
forall a. a -> Maybe a
Just StakingCredential
sc)) (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (TxOutDatum Datum -> Maybe (TxOutDatum Datum))
-> TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a b. (a -> b) -> a -> b
$ Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumHash Datum
datum) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# DEPRECATED mustPayWithDatumInTxToPubKeyAddress "Use mustPayToPubKeyAddressWithDatumInTx instead" #-}
mustPayWithDatumInTxToPubKeyAddress
    :: forall i o
     . PaymentPubKeyHash
    -> StakingCredential
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayWithDatumInTxToPubKeyAddress :: PaymentPubKeyHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayWithDatumInTxToPubKeyAddress = PaymentPubKeyHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
forall i o.
PaymentPubKeyHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToPubKeyAddressWithDatumInTx

{-# INLINABLE mustPayToPubKeyAddressWithDatumInTx #-}
-- | @mustPayToPubKeyAddressWithDatumInTx pkh d v@ is the same as
-- 'mustPayToPubKeyAddressWithDatumHash', but the datum is also added in the
-- transaction body.
mustPayToPubKeyAddressWithDatumInTx
    :: forall i o
     . PaymentPubKeyHash
    -> StakingCredential
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayToPubKeyAddressWithDatumInTx :: PaymentPubKeyHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToPubKeyAddressWithDatumInTx (PaymentPubKeyHash PubKeyHash
pkh) StakingCredential
sc Datum
datum Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (PubKeyHash -> Credential
PubKeyCredential PubKeyHash
pkh) (StakingCredential -> Maybe StakingCredential
forall a. a -> Maybe a
Just StakingCredential
sc)) (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (TxOutDatum Datum -> Maybe (TxOutDatum Datum))
-> TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a b. (a -> b) -> a -> b
$ Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumInTx Datum
datum) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# DEPRECATED mustPayWithInlineDatumToPubKeyAddress "Use mustPayToPubKeyAddressWithInlineDatum instead" #-}
mustPayWithInlineDatumToPubKeyAddress
    :: forall i o
     . PaymentPubKeyHash
    -> StakingCredential
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayWithInlineDatumToPubKeyAddress :: PaymentPubKeyHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayWithInlineDatumToPubKeyAddress = PaymentPubKeyHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
forall i o.
PaymentPubKeyHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToPubKeyAddressWithInlineDatum

{-# INLINABLE mustPayToPubKeyAddressWithInlineDatum #-}
-- | @mustPayWithInlineInlineDatumToPubKeyAddress pkh d v@ is the same as
-- 'mustPayToPubKeyAddressWithInlineDatum', but the datum is inline in the Tx.
mustPayToPubKeyAddressWithInlineDatum
    :: forall i o
     . PaymentPubKeyHash
    -> StakingCredential
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayToPubKeyAddressWithInlineDatum :: PaymentPubKeyHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToPubKeyAddressWithInlineDatum (PaymentPubKeyHash PubKeyHash
pkh) StakingCredential
sc Datum
datum Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (PubKeyHash -> Credential
PubKeyCredential PubKeyHash
pkh) (StakingCredential -> Maybe StakingCredential
forall a. a -> Maybe a
Just StakingCredential
sc)) (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (TxOutDatum Datum -> Maybe (TxOutDatum Datum))
-> TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a b. (a -> b) -> a -> b
$ Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumInline Datum
datum) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# INLINABLE mustPayToAddressWithReferenceValidator #-}
-- | @mustPayToAddressWithReferenceValidator@ is a helper that calls @mustPayToAddressWithReferenceScript@.
mustPayToAddressWithReferenceValidator
    :: forall i o
    . Address
    -> ValidatorHash
    -> Maybe (TxOutDatum Datum)
    -> Value
    -> TxConstraints i o
mustPayToAddressWithReferenceValidator :: Address
-> ValidatorHash
-> Maybe (TxOutDatum Datum)
-> Value
-> TxConstraints i o
mustPayToAddressWithReferenceValidator Address
addr (ValidatorHash BuiltinByteString
vh) = Address
-> ScriptHash
-> Maybe (TxOutDatum Datum)
-> Value
-> TxConstraints i o
forall i o.
Address
-> ScriptHash
-> Maybe (TxOutDatum Datum)
-> Value
-> TxConstraints i o
mustPayToAddressWithReferenceScript Address
addr (BuiltinByteString -> ScriptHash
ScriptHash BuiltinByteString
vh)

{-# INLINABLE mustPayToAddressWithReferenceMintingPolicy #-}
-- | @mustPayToAddressWithReferenceMintingPolicy@ is a helper that calls @mustPayToAddressWithReferenceScript@.
mustPayToAddressWithReferenceMintingPolicy
    :: forall i o
    . Address
    -> MintingPolicyHash
    -> Maybe (TxOutDatum Datum)
    -> Value
    -> TxConstraints i o
mustPayToAddressWithReferenceMintingPolicy :: Address
-> MintingPolicyHash
-> Maybe (TxOutDatum Datum)
-> Value
-> TxConstraints i o
mustPayToAddressWithReferenceMintingPolicy Address
addr (MintingPolicyHash BuiltinByteString
vh) = Address
-> ScriptHash
-> Maybe (TxOutDatum Datum)
-> Value
-> TxConstraints i o
forall i o.
Address
-> ScriptHash
-> Maybe (TxOutDatum Datum)
-> Value
-> TxConstraints i o
mustPayToAddressWithReferenceScript Address
addr (BuiltinByteString -> ScriptHash
ScriptHash BuiltinByteString
vh)

{-# INLINABLE mustPayToAddressWithReferenceScript #-}
-- | @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 'Ledger.Constraints.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 'Ledger.Constraints.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.
mustPayToAddressWithReferenceScript
    :: forall i o
    . Address
    -> ScriptHash
    -> Maybe (TxOutDatum Datum)
    -> Value
    -> TxConstraints i o
mustPayToAddressWithReferenceScript :: Address
-> ScriptHash
-> Maybe (TxOutDatum Datum)
-> Value
-> TxConstraints i o
mustPayToAddressWithReferenceScript Address
addr ScriptHash
scriptHash Maybe (TxOutDatum Datum)
datum Value
value =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress Address
addr Maybe (TxOutDatum Datum)
datum (ScriptHash -> Maybe ScriptHash
forall a. a -> Maybe a
Just ScriptHash
scriptHash) Value
value)

{-# DEPRECATED mustPayToOtherScript "Use mustPayToOtherScriptWithDatumHash instead" #-}
mustPayToOtherScript :: forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o
mustPayToOtherScript :: ValidatorHash -> Datum -> Value -> TxConstraints i o
mustPayToOtherScript = ValidatorHash -> Datum -> Value -> TxConstraints i o
forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptWithDatumHash

{-# INLINABLE mustPayToOtherScriptWithDatumHash #-}
-- | @mustPayToOtherScriptWithDatumHash vh d v@ is the same as
-- 'mustPayToOtherScriptAddressWithDatumHash', but without the staking key hash.
mustPayToOtherScriptWithDatumHash :: forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptWithDatumHash :: ValidatorHash -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptWithDatumHash ValidatorHash
vh Datum
dv Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (ValidatorHash -> Credential
ScriptCredential ValidatorHash
vh) Maybe StakingCredential
forall a. Maybe a
Nothing) (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumHash Datum
dv)) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# INLINABLE mustPayToOtherScriptWithDatumInTx #-}
-- | @mustPayToOtherScriptWithDatumInTx vh d v@ is the same as
-- 'mustPayToOtherScriptAddressWithDatumHash', but without the staking key hash.
mustPayToOtherScriptWithDatumInTx :: forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptWithDatumInTx :: ValidatorHash -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptWithDatumInTx ValidatorHash
vh Datum
dv Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (ValidatorHash -> Credential
ScriptCredential ValidatorHash
vh) Maybe StakingCredential
forall a. Maybe a
Nothing) (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumInTx Datum
dv)) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# INLINABLE mustPayToOtherScriptWithInlineDatum #-}
-- | @mustPayToOtherScriptWithInlineDatum vh d v@ is the same as
-- 'mustPayToOtherScriptAddressWithDatumHash', but with an inline datum and without the staking key hash.
mustPayToOtherScriptWithInlineDatum :: forall i o. ValidatorHash -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptWithInlineDatum :: ValidatorHash -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptWithInlineDatum ValidatorHash
vh Datum
dv Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (ValidatorHash -> Credential
ScriptCredential ValidatorHash
vh) Maybe StakingCredential
forall a. Maybe a
Nothing) (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumInline Datum
dv)) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# DEPRECATED mustPayToOtherScriptAddress "Use mustPayToOtherScriptAddressWithDatumHash instead" #-}
mustPayToOtherScriptAddress :: forall i o. ValidatorHash -> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptAddress :: ValidatorHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptAddress = ValidatorHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
forall i o.
ValidatorHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptAddressWithDatumHash

{-# INLINABLE mustPayToOtherScriptAddressWithDatumHash #-}
-- | @mustPayToOtherScriptAddressWithDatumHash vh svh d v@ locks the value @v@ with the given script
-- hash @vh@ alonside a datum @d@.
--
-- If used in 'Ledger.Constraints.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 'Ledger.Constraints.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.
mustPayToOtherScriptAddressWithDatumHash :: forall i o. ValidatorHash -> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptAddressWithDatumHash :: ValidatorHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptAddressWithDatumHash ValidatorHash
vh StakingCredential
sc Datum
dv Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (ValidatorHash -> Credential
ScriptCredential ValidatorHash
vh) (StakingCredential -> Maybe StakingCredential
forall a. a -> Maybe a
Just StakingCredential
sc)) (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumHash Datum
dv)) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# INLINABLE mustPayToOtherScriptAddressWithDatumInTx #-}
-- | @mustPayToOtherScriptAddressWithDatumInTx vh svh d v@ locks the value @v@ with the given script
-- hash @vh@ alonside a datum @d@.
--
-- If used in 'Ledger.Constraints.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 'Ledger.Constraints.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
mustPayToOtherScriptAddressWithDatumInTx :: ValidatorHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptAddressWithDatumInTx ValidatorHash
vh StakingCredential
sc Datum
dv Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (ValidatorHash -> Credential
ScriptCredential ValidatorHash
vh) (StakingCredential -> Maybe StakingCredential
forall a. a -> Maybe a
Just StakingCredential
sc)) (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumInTx Datum
dv)) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# INLINABLE mustPayToOtherScriptAddressWithInlineDatum #-}
-- | @mustPayToOtherScriptAddressInlineDatum vh d v@ is the same as
-- 'mustPayToOtherScriptAddressWithDatumHash', but with an inline datum.
mustPayToOtherScriptAddressWithInlineDatum
    :: forall i o. ValidatorHash
    -> StakingCredential
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayToOtherScriptAddressWithInlineDatum :: ValidatorHash
-> StakingCredential -> Datum -> Value -> TxConstraints i o
mustPayToOtherScriptAddressWithInlineDatum ValidatorHash
vh StakingCredential
sc Datum
dv Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress (Credential -> Maybe StakingCredential -> Address
Address (ValidatorHash -> Credential
ScriptCredential ValidatorHash
vh) (StakingCredential -> Maybe StakingCredential
forall a. a -> Maybe a
Just StakingCredential
sc)) (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumInline Datum
dv)) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# INLINABLE mustPayToAddress #-}
-- | @mustPayToAddress addr v@ locks the value @v@ at the given address @addr@.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint creates a script
-- output with @addr@ and @v@.
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies
-- that the script transaction output with
-- @addr@ and @v@ is part of the transaction's outputs.
mustPayToAddress :: forall i o. Address -> Value -> TxConstraints i o
mustPayToAddress :: Address -> Value -> TxConstraints i o
mustPayToAddress Address
addr Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress Address
addr Maybe (TxOutDatum Datum)
forall a. Maybe a
Nothing Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# DEPRECATED mustPayToAddressWithDatum "Use mustPayToAddressWithDatumHash instead" #-}
mustPayToAddressWithDatum :: forall i o. Address -> Datum -> Value -> TxConstraints i o
mustPayToAddressWithDatum :: Address -> Datum -> Value -> TxConstraints i o
mustPayToAddressWithDatum = Address -> Datum -> Value -> TxConstraints i o
forall i o. Address -> Datum -> Value -> TxConstraints i o
mustPayToAddressWithDatumHash

{-# INLINABLE mustPayToAddressWithDatumHash #-}
-- | @mustPayToAddress addr d v@ locks the value @v@
-- at the given address @addr@ alonside a datum @d@.
--
-- If used in 'Ledger.Constraints.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 'Ledger.Constraints.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.
mustPayToAddressWithDatumHash :: forall i o. Address -> Datum -> Value -> TxConstraints i o
mustPayToAddressWithDatumHash :: Address -> Datum -> Value -> TxConstraints i o
mustPayToAddressWithDatumHash Address
addr Datum
dv Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress Address
addr (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumHash Datum
dv)) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# INLINABLE mustPayToAddressWithDatumInTx #-}
-- | @mustPayToAddressWithDatumInTx addr d v@ locks the value @v@
-- at the given address @addr@ alonside a datum @d@.
--
-- If used in 'Ledger.Constraints.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 'Ledger.Constraints.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.
mustPayToAddressWithDatumInTx
    :: forall i o. Address
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayToAddressWithDatumInTx :: Address -> Datum -> Value -> TxConstraints i o
mustPayToAddressWithDatumInTx Address
addr Datum
dv Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress Address
addr (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumInTx Datum
dv)) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# INLINABLE mustPayToAddressWithInlineDatum #-}
-- | @mustPayToAddressWithInlineDatum vh d v@ is the same as
-- 'mustPayToAddress', but with an inline datum.
mustPayToAddressWithInlineDatum
    :: forall i o. Address
    -> Datum
    -> Value
    -> TxConstraints i o
mustPayToAddressWithInlineDatum :: Address -> Datum -> Value -> TxConstraints i o
mustPayToAddressWithInlineDatum Address
addr Datum
dv Value
vl =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (Address
-> Maybe (TxOutDatum Datum)
-> Maybe ScriptHash
-> Value
-> TxConstraint
MustPayToAddress Address
addr (TxOutDatum Datum -> Maybe (TxOutDatum Datum)
forall a. a -> Maybe a
Just (Datum -> TxOutDatum Datum
forall datum. datum -> TxOutDatum datum
TxOutDatumInline Datum
dv)) Maybe ScriptHash
forall a. Maybe a
Nothing Value
vl)

{-# INLINABLE mustMintValue #-}
-- | Same as 'mustMintValueWithRedeemer', but sets the redeemer to the unit
-- redeemer.
mustMintValue :: forall i o. Value -> TxConstraints i o
mustMintValue :: Value -> TxConstraints i o
mustMintValue = Redeemer -> Value -> TxConstraints i o
forall i o. Redeemer -> Value -> TxConstraints i o
mustMintValueWithRedeemer Redeemer
unitRedeemer

{-# INLINABLE mustMintValueWithReference #-}
-- | Same as 'mustMintValueWithRedeemerAndReference', but sets the redeemer to the unit
-- redeemer.
mustMintValueWithReference :: forall i o. TxOutRef -> Value -> TxConstraints i o
mustMintValueWithReference :: TxOutRef -> Value -> TxConstraints i o
mustMintValueWithReference = Redeemer -> Maybe TxOutRef -> Value -> TxConstraints i o
forall i o.
Redeemer -> Maybe TxOutRef -> Value -> TxConstraints i o
mustMintValueWithRedeemerAndReference Redeemer
unitRedeemer (Maybe TxOutRef -> Value -> TxConstraints i o)
-> (TxOutRef -> Maybe TxOutRef)
-> TxOutRef
-> Value
-> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOutRef -> Maybe TxOutRef
forall a. a -> Maybe a
Just

{-# INLINABLE mustMintValueWithRedeemer #-}
-- | Same as 'mustMintValueWithRedeemerAndReference', but sets the reference to 'Nothing'.
mustMintValueWithRedeemer :: forall i o. Redeemer -> Value -> TxConstraints i o
mustMintValueWithRedeemer :: Redeemer -> Value -> TxConstraints i o
mustMintValueWithRedeemer Redeemer
red = Redeemer -> Maybe TxOutRef -> Value -> TxConstraints i o
forall i o.
Redeemer -> Maybe TxOutRef -> Value -> TxConstraints i o
mustMintValueWithRedeemerAndReference Redeemer
red Maybe TxOutRef
forall a. Maybe a
Nothing

{-# INLINABLE mustMintValueWithRedeemerAndReference #-}
-- | Same as 'mustMintCurrencyWithRedeemerAndReference', but uses the minting policy hash,
-- token name and amount provided by 'Value'.
--
-- Note that we can derive the 'MintingPolicyHash' from the 'Value'\'s currency
-- symbol.
mustMintValueWithRedeemerAndReference :: forall i o. Redeemer -> Maybe TxOutRef -> Value -> TxConstraints i o
mustMintValueWithRedeemerAndReference :: Redeemer -> Maybe TxOutRef -> Value -> TxConstraints i o
mustMintValueWithRedeemerAndReference Redeemer
red Maybe TxOutRef
mref =
    ((CurrencySymbol, Map TokenName Integer) -> TxConstraints i o)
-> [(CurrencySymbol, Map TokenName Integer)] -> TxConstraints i o
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (CurrencySymbol, Map TokenName Integer) -> TxConstraints i o
valueConstraint ([(CurrencySymbol, Map TokenName Integer)] -> TxConstraints i o)
-> (Value -> [(CurrencySymbol, Map TokenName Integer)])
-> Value
-> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map CurrencySymbol (Map TokenName Integer)
-> [(CurrencySymbol, Map TokenName Integer)]
forall k v. Map k v -> [(k, v)]
AssocMap.toList (Map CurrencySymbol (Map TokenName Integer)
 -> [(CurrencySymbol, Map TokenName Integer)])
-> (Value -> Map CurrencySymbol (Map TokenName Integer))
-> Value
-> [(CurrencySymbol, Map TokenName Integer)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> Map CurrencySymbol (Map TokenName Integer)
Value.getValue)
    where
        valueConstraint :: (CurrencySymbol, Map TokenName Integer) -> TxConstraints i o
valueConstraint (CurrencySymbol
currencySymbol, Map TokenName Integer
mp) =
            let hs :: MintingPolicyHash
hs = CurrencySymbol -> MintingPolicyHash
Value.currencyMPSHash CurrencySymbol
currencySymbol in
            ((TokenName, Integer) -> TxConstraints i o)
-> [(TokenName, Integer)] -> TxConstraints i o
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((TokenName -> Integer -> TxConstraints i o)
-> (TokenName, Integer) -> TxConstraints i o
forall a b c. (a -> b -> c) -> (a, b) -> c
Haskell.uncurry (Maybe TxOutRef
-> MintingPolicyHash
-> Redeemer
-> TokenName
-> Integer
-> TxConstraints i o
forall i o.
Maybe TxOutRef
-> MintingPolicyHash
-> Redeemer
-> TokenName
-> Integer
-> TxConstraints i o
mustMintCurrencyWithRedeemerAndReference Maybe TxOutRef
mref MintingPolicyHash
hs Redeemer
red))
                    (Map TokenName Integer -> [(TokenName, Integer)]
forall k v. Map k v -> [(k, v)]
AssocMap.toList Map TokenName Integer
mp)

{-# INLINABLE mustMintCurrency #-}
-- | Same as 'mustMintCurrencyWithRedeemer', but sets the redeemer to the unit
-- redeemer.
mustMintCurrency
    :: forall i o
     . MintingPolicyHash
    -> TokenName
    -> Integer
    -> TxConstraints i o
mustMintCurrency :: MintingPolicyHash -> TokenName -> Integer -> TxConstraints i o
mustMintCurrency MintingPolicyHash
mps = MintingPolicyHash
-> Redeemer -> TokenName -> Integer -> TxConstraints i o
forall i o.
MintingPolicyHash
-> Redeemer -> TokenName -> Integer -> TxConstraints i o
mustMintCurrencyWithRedeemer MintingPolicyHash
mps Redeemer
unitRedeemer

{-# INLINABLE mustMintCurrencyWithReference #-}
-- | Same as 'mustMintCurrencyWithRedeemerAndReference', but sets the redeemer to the unit
-- redeemer.
mustMintCurrencyWithReference
    :: forall i o
     . TxOutRef
    -> MintingPolicyHash
    -> TokenName
    -> Integer
    -> TxConstraints i o
mustMintCurrencyWithReference :: TxOutRef
-> MintingPolicyHash -> TokenName -> Integer -> TxConstraints i o
mustMintCurrencyWithReference TxOutRef
ref MintingPolicyHash
mps = Maybe TxOutRef
-> MintingPolicyHash
-> Redeemer
-> TokenName
-> Integer
-> TxConstraints i o
forall i o.
Maybe TxOutRef
-> MintingPolicyHash
-> Redeemer
-> TokenName
-> Integer
-> TxConstraints i o
mustMintCurrencyWithRedeemerAndReference (TxOutRef -> Maybe TxOutRef
forall a. a -> Maybe a
Just TxOutRef
ref) MintingPolicyHash
mps Redeemer
unitRedeemer

{-# INLINABLE mustMintCurrencyWithRedeemer #-}
-- | Same as 'mustMintCurrencyWithRedeemerAndReference', but sets the reference to 'Nothing'.
mustMintCurrencyWithRedeemer
    :: forall i o
     . MintingPolicyHash
    -> Redeemer
    -> TokenName
    -> Integer
    -> TxConstraints i o
mustMintCurrencyWithRedeemer :: MintingPolicyHash
-> Redeemer -> TokenName -> Integer -> TxConstraints i o
mustMintCurrencyWithRedeemer = Maybe TxOutRef
-> MintingPolicyHash
-> Redeemer
-> TokenName
-> Integer
-> TxConstraints i o
forall i o.
Maybe TxOutRef
-> MintingPolicyHash
-> Redeemer
-> TokenName
-> Integer
-> TxConstraints i o
mustMintCurrencyWithRedeemerAndReference Maybe TxOutRef
forall a. Maybe a
Nothing

{-# INLINABLE mustMintCurrencyWithRedeemerAndReference #-}
-- | @mustMintCurrencyWithRedeemerAndReference mref mph r tn a@ creates the given amount @a@ of
-- the currency specified with @mph@, @r@ and @tn@. The minting policy script can be specified
-- with a reference script @mref@.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint mints a currency
-- using @mref@, @mph@, @r@, @tn@ and @a@, adds @mph@ in the transaction's minting
-- policy witness set and adds @r@ in the transaction's redeemer witness set.
-- The minting policy must be provided in the
-- 'Ledger.Constraints.OffChain.ScriptLookups' with
-- 'Ledger.Constraints.OffChain.typedValidatorLookups' or
-- 'Ledger.Constraints.OffChain.plutusV1MintingPolicy'.
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies that the
-- minted currenty @mref@, @mph@, @tn@ and @a@ is part of the transaction's minting
-- information.
mustMintCurrencyWithRedeemerAndReference
    :: forall i o
     . Maybe TxOutRef
    -> MintingPolicyHash
    -> Redeemer
    -> TokenName
    -> Integer
    -> TxConstraints i o
mustMintCurrencyWithRedeemerAndReference :: Maybe TxOutRef
-> MintingPolicyHash
-> Redeemer
-> TokenName
-> Integer
-> TxConstraints i o
mustMintCurrencyWithRedeemerAndReference Maybe TxOutRef
mref MintingPolicyHash
mph Redeemer
red TokenName
tn Integer
a =
  if Integer
a Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0 then TxConstraints i o
forall a. Monoid a => a
mempty else TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> TxConstraint -> TxConstraints i o
forall a b. (a -> b) -> a -> b
$ MintingPolicyHash
-> Redeemer
-> TokenName
-> Integer
-> Maybe TxOutRef
-> TxConstraint
MustMintValue MintingPolicyHash
mph Redeemer
red TokenName
tn Integer
a Maybe TxOutRef
mref

{-# INLINABLE mustSpendAtLeast #-}
-- | @mustSpendAtLeast v@ requires the sum of the transaction's inputs value to
-- be at least @v@.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint checks if
-- at least the given value is spent in the transaction.
-- When the transaction is created, a 'MkTxError.DeclaredInputMismatch' error
-- is raised if it is not the case.
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies that the
-- sum of the transaction's inputs value to be at least @v@.
mustSpendAtLeast :: forall i o. Value -> TxConstraints i o
mustSpendAtLeast :: Value -> TxConstraints i o
mustSpendAtLeast = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> (Value -> TxConstraint) -> Value -> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> TxConstraint
MustSpendAtLeast

{-# INLINABLE mustProduceAtLeast #-}
-- | @mustProduceAtLeast v@ requires the sum of the transaction's outputs value to
-- be at least @v@.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint checks if
-- at least the given value is produced in the transaction.
-- When the transaction is created, a 'MkTxError.DeclaredOutputMismatch' error
-- is raised if it is not the case.
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies that the
-- sum of the transaction's outputs value to be at least @v@.
mustProduceAtLeast :: forall i o. Value -> TxConstraints i o
mustProduceAtLeast :: Value -> TxConstraints i o
mustProduceAtLeast = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> (Value -> TxConstraint) -> Value -> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Value -> TxConstraint
MustProduceAtLeast

{-# INLINABLE mustSpendPubKeyOutput #-}
-- | @mustSpendPubKeyOutput utxo@ must spend the given unspent transaction public key output.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint adds @utxo@ as an
-- input to the transaction. Information about this @utxo@ must be provided in
-- the 'Ledger.Constraints.OffChain.ScriptLookups' with
-- 'Ledger.Constraints.OffChain.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 'Ledger.Constraints.OnChain', this constraint verifies that the
-- transaction spends this @utxo@.
mustSpendPubKeyOutput :: forall i o. TxOutRef -> TxConstraints i o
mustSpendPubKeyOutput :: TxOutRef -> TxConstraints i o
mustSpendPubKeyOutput = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> (TxOutRef -> TxConstraint) -> TxOutRef -> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOutRef -> TxConstraint
MustSpendPubKeyOutput

{-# INLINABLE mustSpendScriptOutput #-}
-- | @mustSpendScriptOutput utxo red@ must spend the given unspent transaction script output.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint adds @utxo@ and
-- @red@ as an input to the transaction. Information about this @utxo@ must be
-- provided in the 'Ledger.Constraints.OffChain.ScriptLookups' with
-- 'Ledger.Constraints.OffChain.unspentOutputs'. The validator must be either provided by
-- 'Ledger.Constraints.OffChain.unspentOutputs' or through
-- 'Ledger.Constraints.OffChain.otherScript' . The datum must be either provided by
-- 'Ledger.Constraints.OffChain.unspentOutputs' or through
-- 'Ledger.Constraints.OffChain.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 'Ledger.Constraints.OnChain', this constraint verifies that the
-- transaction spends this @utxo@.
mustSpendScriptOutput :: forall i o. TxOutRef -> Redeemer -> TxConstraints i o
mustSpendScriptOutput :: TxOutRef -> Redeemer -> TxConstraints i o
mustSpendScriptOutput TxOutRef
txOutref Redeemer
red = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> TxConstraint -> TxConstraints i o
forall a b. (a -> b) -> a -> b
$ TxOutRef -> Redeemer -> Maybe TxOutRef -> TxConstraint
MustSpendScriptOutput TxOutRef
txOutref Redeemer
red Maybe TxOutRef
forall a. Maybe a
Nothing

{-# INLINABLE mustSpendScriptOutputWithReference #-}
-- | @mustSpendScriptOutputWithReference utxo red refTxOutref@ must spend the given unspent
-- transaction script output, using a script reference as witness.
--
-- If used in 'Ledger.Constraints.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 'Ledger.Constraints.OffChain.ScriptLookups' with
-- 'Ledger.Constraints.OffChain.unspentOutputs'. The datum must be either provided by
-- 'Ledger.Constraints.OffChain.unspentOutputs' or through
-- 'Ledger.Constraints.OffChain.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 'Ledger.Constraints.OnChain', this constraint verifies that the
-- transaction spends this @utxo@.
mustSpendScriptOutputWithReference :: TxOutRef -> Redeemer -> TxOutRef -> TxConstraints i o
mustSpendScriptOutputWithReference :: TxOutRef -> Redeemer -> TxOutRef -> TxConstraints i o
mustSpendScriptOutputWithReference TxOutRef
txOutref Redeemer
red TxOutRef
refTxOutref =
    TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxOutRef -> Redeemer -> Maybe TxOutRef -> TxConstraint
MustSpendScriptOutput TxOutRef
txOutref Redeemer
red (TxOutRef -> Maybe TxOutRef
forall a. a -> Maybe a
Just TxOutRef
refTxOutref))

{-# INLINABLE mustSpendScriptOutputWithMatchingDatumAndValue #-}
-- | @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 'Ledger.Constraints.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 'Ledger.Constraints.OffChain.ScriptLookups' with
-- 'Ledger.Constraints.OffChain.unspentOutputs'.
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies that there's at least one input
-- that matches the requirements.
mustSpendScriptOutputWithMatchingDatumAndValue
    :: forall i o. ValidatorHash
    -> (Datum -> Bool)
    -> (Value -> Bool)
    -> Redeemer
    -> TxConstraints i o
mustSpendScriptOutputWithMatchingDatumAndValue :: ValidatorHash
-> (Datum -> Bool)
-> (Value -> Bool)
-> Redeemer
-> TxConstraints i o
mustSpendScriptOutputWithMatchingDatumAndValue ValidatorHash
vh Datum -> Bool
datumPred Value -> Bool
valuePred Redeemer
red =
    TxConstraints i o
forall a. Monoid a => a
mempty {
        txConstraintFuns :: TxConstraintFuns
txConstraintFuns = [TxConstraintFun] -> TxConstraintFuns
TxConstraintFuns [ValidatorHash
-> (Datum -> Bool)
-> (Value -> Bool)
-> Redeemer
-> TxConstraintFun
MustSpendScriptOutputWithMatchingDatumAndValue ValidatorHash
vh Datum -> Bool
datumPred Value -> Bool
valuePred Redeemer
red ]
    }

{-# INLINABLE mustUseOutputAsCollateral #-}
-- | @mustUseOutputAsCollateral utxo@ must use the given unspent transaction output
-- reference as collateral input.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint adds @utxo@ as a
-- collateral input to the transaction.
--
-- In 'Ledger.Constraints.OnChain' this constraint has no effect, since
-- no information about collateral inputs is passed to the scripts.
mustUseOutputAsCollateral :: forall i o. TxOutRef -> TxConstraints i o
mustUseOutputAsCollateral :: TxOutRef -> TxConstraints i o
mustUseOutputAsCollateral = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> (TxOutRef -> TxConstraint) -> TxOutRef -> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOutRef -> TxConstraint
MustUseOutputAsCollateral

{-# INLINABLE mustReferenceOutput #-}
-- | @mustReferenceOutput utxo@ must reference (not spend!) the given
-- unspent transaction output reference.
--
-- If used in 'Ledger.Constraints.OffChain', this constraint adds @utxo@ as a
-- reference input to the transaction.
--
-- If used in 'Ledger.Constraints.OnChain', this constraint verifies that the
-- transaction references this @utxo@.
mustReferenceOutput :: forall i o. TxOutRef -> TxConstraints i o
mustReferenceOutput :: TxOutRef -> TxConstraints i o
mustReferenceOutput = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> (TxOutRef -> TxConstraint) -> TxOutRef -> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxOutRef -> TxConstraint
MustReferenceOutput

{-# INLINABLE mustSatisfyAnyOf #-}
mustSatisfyAnyOf :: forall i o. [TxConstraints i o] -> TxConstraints i o
mustSatisfyAnyOf :: [TxConstraints i o] -> TxConstraints i o
mustSatisfyAnyOf = TxConstraint -> TxConstraints i o
forall i o. TxConstraint -> TxConstraints i o
singleton (TxConstraint -> TxConstraints i o)
-> ([TxConstraints i o] -> TxConstraint)
-> [TxConstraints i o]
-> TxConstraints i o
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [[TxConstraint]] -> TxConstraint
MustSatisfyAnyOf ([[TxConstraint]] -> TxConstraint)
-> ([TxConstraints i o] -> [[TxConstraint]])
-> [TxConstraints i o]
-> TxConstraint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxConstraints i o -> [TxConstraint])
-> [TxConstraints i o] -> [[TxConstraint]]
forall a b. (a -> b) -> [a] -> [b]
map TxConstraints i o -> [TxConstraint]
forall i o. TxConstraints i o -> [TxConstraint]
txConstraints

{-# INLINABLE isSatisfiable #-}
-- | Are the constraints satisfiable?
isSatisfiable :: forall i o. TxConstraints i o -> Bool
isSatisfiable :: TxConstraints i o -> Bool
isSatisfiable TxConstraints{[TxConstraint]
txConstraints :: [TxConstraint]
txConstraints :: forall i o. TxConstraints i o -> [TxConstraint]
txConstraints} =
    let intervals :: [ValidityInterval POSIXTime]
intervals = (TxConstraint -> Maybe (ValidityInterval POSIXTime))
-> [TxConstraint] -> [ValidityInterval POSIXTime]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (\case { MustValidateInTimeRange ValidityInterval POSIXTime
i -> ValidityInterval POSIXTime -> Maybe (ValidityInterval POSIXTime)
forall a. a -> Maybe a
Just ValidityInterval POSIXTime
i; TxConstraint
_ -> Maybe (ValidityInterval POSIXTime)
forall a. Maybe a
Nothing }) [TxConstraint]
txConstraints
        itvl :: POSIXTimeRange
itvl = (POSIXTimeRange -> POSIXTimeRange -> POSIXTimeRange)
-> POSIXTimeRange -> [POSIXTimeRange] -> POSIXTimeRange
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl POSIXTimeRange -> POSIXTimeRange -> POSIXTimeRange
forall a. Ord a => Interval a -> Interval a -> Interval a
I.intersection POSIXTimeRange
forall a. Interval a
I.always ([POSIXTimeRange] -> POSIXTimeRange)
-> [POSIXTimeRange] -> POSIXTimeRange
forall a b. (a -> b) -> a -> b
$ (ValidityInterval POSIXTime -> POSIXTimeRange)
-> [ValidityInterval POSIXTime] -> [POSIXTimeRange]
forall a b. (a -> b) -> [a] -> [b]
map ValidityInterval POSIXTime -> POSIXTimeRange
forall a. ValidityInterval a -> Interval a
toPlutusInterval [ValidityInterval POSIXTime]
intervals
    in Bool -> Bool
not (POSIXTimeRange -> Bool
forall a. (Enum a, Ord a) => Interval a -> Bool
I.isEmpty POSIXTimeRange
itvl)

{-# INLINABLE pubKeyPayments #-}
pubKeyPayments :: forall i o. TxConstraints i o -> [(PaymentPubKeyHash, Value)]
pubKeyPayments :: TxConstraints i o -> [(PaymentPubKeyHash, Value)]
pubKeyPayments TxConstraints{[TxConstraint]
txConstraints :: [TxConstraint]
txConstraints :: forall i o. TxConstraints i o -> [TxConstraint]
txConstraints} =
    Map PaymentPubKeyHash Value -> [(PaymentPubKeyHash, Value)]
forall k a. Map k a -> [(k, a)]
Map.toList
    (Map PaymentPubKeyHash Value -> [(PaymentPubKeyHash, Value)])
-> Map PaymentPubKeyHash Value -> [(PaymentPubKeyHash, Value)]
forall a b. (a -> b) -> a -> b
$ (Value -> Value -> Value)
-> [(PaymentPubKeyHash, Value)] -> Map PaymentPubKeyHash Value
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Map.fromListWith Value -> Value -> Value
forall a. Semigroup a => a -> a -> a
(<>)
      ([TxConstraint]
txConstraints [TxConstraint]
-> (TxConstraint -> [(PaymentPubKeyHash, Value)])
-> [(PaymentPubKeyHash, Value)]
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case { MustPayToAddress (Address (PubKeyCredential PubKeyHash
pk) Maybe StakingCredential
_) Maybe (TxOutDatum Datum)
_ Maybe ScriptHash
_ Value
vl -> [(PubKeyHash -> PaymentPubKeyHash
PaymentPubKeyHash PubKeyHash
pk, Value
vl)]; TxConstraint
_ -> [] })

-- | The minimum 'Value' that satisfies all 'MustSpendAtLeast' constraints
{-# INLINABLE mustSpendAtLeastTotal #-}
mustSpendAtLeastTotal :: forall i o. TxConstraints i o -> Value
mustSpendAtLeastTotal :: TxConstraints i o -> Value
mustSpendAtLeastTotal = (Value -> Value -> Value) -> Value -> [Value] -> Value
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Value -> Value -> Value
forall a. JoinSemiLattice a => a -> a -> a
(\/) Value
forall a. Monoid a => a
mempty ([Value] -> Value)
-> (TxConstraints i o -> [Value]) -> TxConstraints i o -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxConstraint -> Value) -> [TxConstraint] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TxConstraint -> Value
f ([TxConstraint] -> [Value])
-> (TxConstraints i o -> [TxConstraint])
-> TxConstraints i o
-> [Value]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxConstraints i o -> [TxConstraint]
forall i o. TxConstraints i o -> [TxConstraint]
txConstraints where
    f :: TxConstraint -> Value
f (MustSpendAtLeast Value
v) = Value
v
    f TxConstraint
_                    = Value
forall a. Monoid a => a
mempty

-- | The minimum 'Value' that satisfies all 'MustProduceAtLeast' constraints
{-# INLINABLE mustProduceAtLeastTotal #-}
mustProduceAtLeastTotal :: forall i o. TxConstraints i o -> Value
mustProduceAtLeastTotal :: TxConstraints i o -> Value
mustProduceAtLeastTotal = (Value -> Value -> Value) -> Value -> [Value] -> Value
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl Value -> Value -> Value
forall a. JoinSemiLattice a => a -> a -> a
(\/) Value
forall a. Monoid a => a
mempty ([Value] -> Value)
-> (TxConstraints i o -> [Value]) -> TxConstraints i o -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (TxConstraint -> Value) -> [TxConstraint] -> [Value]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap TxConstraint -> Value
f ([TxConstraint] -> [Value])
-> (TxConstraints i o -> [TxConstraint])
-> TxConstraints i o
-> [Value]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxConstraints i o -> [TxConstraint]
forall i o. TxConstraints i o -> [TxConstraint]
txConstraints where
    f :: TxConstraint -> Value
f (MustProduceAtLeast Value
v) = Value
v
    f TxConstraint
_                      = Value
forall a. Monoid a => a
mempty

{-# INLINABLE requiredSignatories #-}
requiredSignatories :: forall i o. TxConstraints i o -> [PaymentPubKeyHash]
requiredSignatories :: TxConstraints i o -> [PaymentPubKeyHash]
requiredSignatories = (TxConstraint -> [PaymentPubKeyHash])
-> [TxConstraint] -> [PaymentPubKeyHash]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap TxConstraint -> [PaymentPubKeyHash]
f ([TxConstraint] -> [PaymentPubKeyHash])
-> (TxConstraints i o -> [TxConstraint])
-> TxConstraints i o
-> [PaymentPubKeyHash]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxConstraints i o -> [TxConstraint]
forall i o. TxConstraints i o -> [TxConstraint]
txConstraints where
    f :: TxConstraint -> [PaymentPubKeyHash]
f (MustBeSignedBy PaymentPubKeyHash
pk) = [PaymentPubKeyHash
pk]
    f TxConstraint
_                   = []

{-# INLINABLE requiredMonetaryPolicies #-}
requiredMonetaryPolicies :: forall i o. TxConstraints i o -> [MintingPolicyHash]
requiredMonetaryPolicies :: TxConstraints i o -> [MintingPolicyHash]
requiredMonetaryPolicies = (TxConstraint -> [MintingPolicyHash])
-> [TxConstraint] -> [MintingPolicyHash]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap TxConstraint -> [MintingPolicyHash]
f ([TxConstraint] -> [MintingPolicyHash])
-> (TxConstraints i o -> [TxConstraint])
-> TxConstraints i o
-> [MintingPolicyHash]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxConstraints i o -> [TxConstraint]
forall i o. TxConstraints i o -> [TxConstraint]
txConstraints where
    f :: TxConstraint -> [MintingPolicyHash]
f (MustMintValue MintingPolicyHash
mps Redeemer
_ TokenName
_ Integer
_ Maybe TxOutRef
_) = [MintingPolicyHash
mps]
    f TxConstraint
_                           = []

{-# INLINABLE requiredDatums #-}
requiredDatums :: forall i o. TxConstraints i o -> [Datum]
requiredDatums :: TxConstraints i o -> [Datum]
requiredDatums = (TxConstraint -> [Datum]) -> [TxConstraint] -> [Datum]
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap TxConstraint -> [Datum]
f ([TxConstraint] -> [Datum])
-> (TxConstraints i o -> [TxConstraint])
-> TxConstraints i o
-> [Datum]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxConstraints i o -> [TxConstraint]
forall i o. TxConstraints i o -> [TxConstraint]
txConstraints where
    f :: TxConstraint -> [Datum]
f (MustIncludeDatumInTx Datum
dv) = [Datum
dv]
    f TxConstraint
_                         = []

{-# INLINABLE modifiesUtxoSet #-}
-- | Check whether every transaction that satisfies the constraints has to
-- modify the UTXO set.
modifiesUtxoSet :: forall i o. TxConstraints i o -> Bool
modifiesUtxoSet :: TxConstraints i o -> Bool
modifiesUtxoSet TxConstraints{[TxConstraint]
txConstraints :: [TxConstraint]
txConstraints :: forall i o. TxConstraints i o -> [TxConstraint]
txConstraints, [ScriptOutputConstraint o]
txOwnOutputs :: [ScriptOutputConstraint o]
txOwnOutputs :: forall i o. TxConstraints i o -> [ScriptOutputConstraint o]
txOwnOutputs, [ScriptInputConstraint i]
txOwnInputs :: [ScriptInputConstraint i]
txOwnInputs :: forall i o. TxConstraints i o -> [ScriptInputConstraint i]
txOwnInputs} =
    let requiresInputOutput :: TxConstraint -> Bool
requiresInputOutput = \case
            MustSpendAtLeast{}        -> Bool
True
            MustProduceAtLeast{}      -> Bool
True
            MustSpendPubKeyOutput{}   -> Bool
True
            MustSpendScriptOutput{}   -> Bool
True
            MustMintValue{}           -> Bool
True
            MustPayToAddress Address
_ Maybe (TxOutDatum Datum)
_ Maybe ScriptHash
_ Value
vl -> Bool -> Bool
not (Value -> Bool
isZero Value
vl)
            MustSatisfyAnyOf [[TxConstraint]]
xs       -> (TxConstraint -> Bool) -> [TxConstraint] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any TxConstraint -> Bool
requiresInputOutput ([TxConstraint] -> Bool) -> [TxConstraint] -> Bool
forall a b. (a -> b) -> a -> b
$ [[TxConstraint]] -> [TxConstraint]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [[TxConstraint]]
xs
            TxConstraint
_                         -> Bool
False
    in (TxConstraint -> Bool) -> [TxConstraint] -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
any TxConstraint -> Bool
requiresInputOutput [TxConstraint]
txConstraints
        Bool -> Bool -> Bool
|| Bool -> Bool
not ([ScriptOutputConstraint o] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ScriptOutputConstraint o]
txOwnOutputs)
        Bool -> Bool -> Bool
|| Bool -> Bool
not ([ScriptInputConstraint i] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [ScriptInputConstraint i]
txOwnInputs)

----------------------
-- Off-chain use only
----------------------

-- | 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.
collectFromPlutusV1Script
    :: Map Address (Map TxOutRef DecoratedTxOut)
    -> Validator
    -> Redeemer
    -> UntypedConstraints
collectFromPlutusV1Script :: Map Address (Map TxOutRef DecoratedTxOut)
-> Validator -> Redeemer -> UntypedConstraints
collectFromPlutusV1Script= (TxOutRef -> DecoratedTxOut -> Bool)
-> Map Address (Map TxOutRef DecoratedTxOut)
-> Validator
-> Redeemer
-> UntypedConstraints
collectFromPlutusV1ScriptFilter (\TxOutRef
_ -> Bool -> DecoratedTxOut -> Bool
forall a b. a -> b -> a
const Bool
True)

collectFromPlutusV1ScriptFilter
    :: (TxOutRef -> DecoratedTxOut -> Bool)
    -> Map Address (Map TxOutRef DecoratedTxOut)
    -> Validator
    -> Redeemer
    -> UntypedConstraints
collectFromPlutusV1ScriptFilter :: (TxOutRef -> DecoratedTxOut -> Bool)
-> Map Address (Map TxOutRef DecoratedTxOut)
-> Validator
-> Redeemer
-> UntypedConstraints
collectFromPlutusV1ScriptFilter TxOutRef -> DecoratedTxOut -> Bool
flt Map Address (Map TxOutRef DecoratedTxOut)
am Validator
vls Redeemer
red =
    let mp' :: Map TxOutRef DecoratedTxOut
mp'  = Map TxOutRef DecoratedTxOut
-> Maybe (Map TxOutRef DecoratedTxOut)
-> Map TxOutRef DecoratedTxOut
forall a. a -> Maybe a -> a
fromMaybe Map TxOutRef DecoratedTxOut
forall a. Monoid a => a
Haskell.mempty (Maybe (Map TxOutRef DecoratedTxOut)
 -> Map TxOutRef DecoratedTxOut)
-> Maybe (Map TxOutRef DecoratedTxOut)
-> Map TxOutRef DecoratedTxOut
forall a b. (a -> b) -> a -> b
$ Map Address (Map TxOutRef DecoratedTxOut)
am Map Address (Map TxOutRef DecoratedTxOut)
-> Getting
     (Maybe (Map TxOutRef DecoratedTxOut))
     (Map Address (Map TxOutRef DecoratedTxOut))
     (Maybe (Map TxOutRef DecoratedTxOut))
-> Maybe (Map TxOutRef DecoratedTxOut)
forall s a. s -> Getting a s a -> a
^. Index (Map Address (Map TxOutRef DecoratedTxOut))
-> Lens'
     (Map Address (Map TxOutRef DecoratedTxOut))
     (Maybe (IxValue (Map Address (Map TxOutRef DecoratedTxOut))))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at (Validator -> Address
PV1.mkValidatorAddress Validator
vls)
        ourUtxo :: Map TxOutRef DecoratedTxOut
ourUtxo = (TxOutRef -> DecoratedTxOut -> Bool)
-> Map TxOutRef DecoratedTxOut -> Map TxOutRef DecoratedTxOut
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey TxOutRef -> DecoratedTxOut -> Bool
flt Map TxOutRef DecoratedTxOut
mp'
    in (TxOutRef -> UntypedConstraints)
-> [TxOutRef] -> UntypedConstraints
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((TxOutRef -> Redeemer -> UntypedConstraints)
-> Redeemer -> TxOutRef -> UntypedConstraints
forall a b c. (a -> b -> c) -> b -> a -> c
flip TxOutRef -> Redeemer -> UntypedConstraints
forall i o. TxOutRef -> Redeemer -> TxConstraints i o
mustSpendScriptOutput Redeemer
red) ([TxOutRef] -> UntypedConstraints)
-> [TxOutRef] -> UntypedConstraints
forall a b. (a -> b) -> a -> b
$ Map TxOutRef DecoratedTxOut -> [TxOutRef]
forall k a. Map k a -> [k]
Map.keys Map TxOutRef DecoratedTxOut
ourUtxo

-- | Given the pay to script address of the 'Validator', collect from it
-- all the outputs that match a predicate, using the 'RedeemerValue'.
collectFromTheScriptFilter ::
    forall i o
    .  (TxOutRef -> DecoratedTxOut -> Bool)
    -> Map.Map TxOutRef DecoratedTxOut
    -> i
    -> TxConstraints i o
collectFromTheScriptFilter :: (TxOutRef -> DecoratedTxOut -> Bool)
-> Map TxOutRef DecoratedTxOut -> i -> TxConstraints i o
collectFromTheScriptFilter TxOutRef -> DecoratedTxOut -> Bool
flt Map TxOutRef DecoratedTxOut
utxo i
red =
    let ourUtxo :: Map.Map TxOutRef DecoratedTxOut
        ourUtxo :: Map TxOutRef DecoratedTxOut
ourUtxo = (TxOutRef -> DecoratedTxOut -> Bool)
-> Map TxOutRef DecoratedTxOut -> Map TxOutRef DecoratedTxOut
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey TxOutRef -> DecoratedTxOut -> Bool
flt Map TxOutRef DecoratedTxOut
utxo
    in Map TxOutRef DecoratedTxOut -> i -> TxConstraints i o
forall i o. Map TxOutRef DecoratedTxOut -> i -> TxConstraints i o
collectFromTheScript Map TxOutRef DecoratedTxOut
ourUtxo i
red

-- | A version of 'collectFromScript' that selects all outputs
-- at the address
collectFromTheScript ::
    forall i o
    .  Map.Map TxOutRef DecoratedTxOut
    -> i
    -> TxConstraints i o
collectFromTheScript :: Map TxOutRef DecoratedTxOut -> i -> TxConstraints i o
collectFromTheScript Map TxOutRef DecoratedTxOut
utxo i
redeemer =
    (TxOutRef -> TxConstraints i o) -> [TxOutRef] -> TxConstraints i o
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((TxOutRef -> i -> TxConstraints i o)
-> i -> TxOutRef -> TxConstraints i o
forall a b c. (a -> b -> c) -> b -> a -> c
flip TxOutRef -> i -> TxConstraints i o
forall i o. TxOutRef -> i -> TxConstraints i o
mustSpendOutputFromTheScript i
redeemer) ([TxOutRef] -> TxConstraints i o)
-> [TxOutRef] -> TxConstraints i o
forall a b. (a -> b) -> a -> b
$ Map TxOutRef DecoratedTxOut -> [TxOutRef]
forall k a. Map k a -> [k]
Map.keys Map TxOutRef DecoratedTxOut
utxo

-- | 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.
collectFromPlutusV2Script
    :: Map Address (Map TxOutRef DecoratedTxOut)
    -> Validator
    -> Redeemer
    -> UntypedConstraints
collectFromPlutusV2Script :: Map Address (Map TxOutRef DecoratedTxOut)
-> Validator -> Redeemer -> UntypedConstraints
collectFromPlutusV2Script= (TxOutRef -> DecoratedTxOut -> Bool)
-> Map Address (Map TxOutRef DecoratedTxOut)
-> Validator
-> Redeemer
-> UntypedConstraints
collectFromPlutusV2ScriptFilter (\TxOutRef
_ -> Bool -> DecoratedTxOut -> Bool
forall a b. a -> b -> a
const Bool
True)

collectFromPlutusV2ScriptFilter
    :: (TxOutRef -> DecoratedTxOut -> Bool)
    -> Map Address (Map TxOutRef DecoratedTxOut)
    -> Validator
    -> Redeemer
    -> UntypedConstraints
collectFromPlutusV2ScriptFilter :: (TxOutRef -> DecoratedTxOut -> Bool)
-> Map Address (Map TxOutRef DecoratedTxOut)
-> Validator
-> Redeemer
-> UntypedConstraints
collectFromPlutusV2ScriptFilter TxOutRef -> DecoratedTxOut -> Bool
flt Map Address (Map TxOutRef DecoratedTxOut)
am Validator
vls Redeemer
red = -- (Redeemer red) =
    -- let mp'  = fromMaybe mempty $ am ^. at (PV2.mkValidatorAddress vls)
    -- in collectFromTheScriptFilter @PlutusTx.BuiltinData @PlutusTx.BuiltinData flt mp' red
    let mp' :: Map TxOutRef DecoratedTxOut
mp'  = Map TxOutRef DecoratedTxOut
-> Maybe (Map TxOutRef DecoratedTxOut)
-> Map TxOutRef DecoratedTxOut
forall a. a -> Maybe a -> a
fromMaybe Map TxOutRef DecoratedTxOut
forall a. Monoid a => a
Haskell.mempty (Maybe (Map TxOutRef DecoratedTxOut)
 -> Map TxOutRef DecoratedTxOut)
-> Maybe (Map TxOutRef DecoratedTxOut)
-> Map TxOutRef DecoratedTxOut
forall a b. (a -> b) -> a -> b
$ Map Address (Map TxOutRef DecoratedTxOut)
am Map Address (Map TxOutRef DecoratedTxOut)
-> Getting
     (Maybe (Map TxOutRef DecoratedTxOut))
     (Map Address (Map TxOutRef DecoratedTxOut))
     (Maybe (Map TxOutRef DecoratedTxOut))
-> Maybe (Map TxOutRef DecoratedTxOut)
forall s a. s -> Getting a s a -> a
^. Index (Map Address (Map TxOutRef DecoratedTxOut))
-> Lens'
     (Map Address (Map TxOutRef DecoratedTxOut))
     (Maybe (IxValue (Map Address (Map TxOutRef DecoratedTxOut))))
forall m. At m => Index m -> Lens' m (Maybe (IxValue m))
at (Validator -> Address
PV2.mkValidatorAddress Validator
vls)
        ourUtxo :: Map TxOutRef DecoratedTxOut
ourUtxo = (TxOutRef -> DecoratedTxOut -> Bool)
-> Map TxOutRef DecoratedTxOut -> Map TxOutRef DecoratedTxOut
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
Map.filterWithKey TxOutRef -> DecoratedTxOut -> Bool
flt Map TxOutRef DecoratedTxOut
mp'
    in (TxOutRef -> UntypedConstraints)
-> [TxOutRef] -> UntypedConstraints
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((TxOutRef -> Redeemer -> UntypedConstraints)
-> Redeemer -> TxOutRef -> UntypedConstraints
forall a b c. (a -> b -> c) -> b -> a -> c
flip TxOutRef -> Redeemer -> UntypedConstraints
forall i o. TxOutRef -> Redeemer -> TxConstraints i o
mustSpendScriptOutput Redeemer
red) ([TxOutRef] -> UntypedConstraints)
-> [TxOutRef] -> UntypedConstraints
forall a b. (a -> b) -> a -> b
$ Map TxOutRef DecoratedTxOut -> [TxOutRef]
forall k a. Map k a -> [k]
Map.keys Map TxOutRef DecoratedTxOut
ourUtxo