{-# LANGUAGE DerivingVia       #-}
{-# LANGUAGE NamedFieldPuns    #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms   #-}
{-# LANGUAGE TemplateHaskell   #-}
{-# LANGUAGE ViewPatterns      #-}
{-# OPTIONS_GHC -Wno-simplifiable-class-constraints #-}
{-# OPTIONS_GHC -fexpose-all-unfoldings #-} -- needed for asData pattern synonyms
{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}
{-# OPTIONS_GHC -fno-specialise #-}

module PlutusLedgerApi.V1.Data.Contexts (
  -- * Pending transactions and related types
  TxInfo,
  pattern TxInfo,
  txInfoInputs,
  txInfoOutputs,
  txInfoFee,
  txInfoMint,
  txInfoDCert,
  txInfoWdrl,
  txInfoValidRange,
  txInfoSignatories,
  txInfoData,
  txInfoId,
  ScriptContext,
  pattern ScriptContext,
  scriptContextTxInfo,
  scriptContextPurpose,
  ScriptPurpose,
  pattern Minting,
  pattern Spending,
  pattern Rewarding,
  pattern Certifying,
  TxId (..),
  TxOut,
  pattern TxOut,
  txOutAddress,
  txOutValue,
  txOutDatumHash,
  TxOutRef,
  pattern TxOutRef,
  txOutRefId,
  txOutRefIdx,
  TxInInfo,
  pattern TxInInfo,
  txInInfoOutRef,
  txInInfoResolved,
  findOwnInput,
  findDatum,
  findDatumHash,
  findTxInByTxOutRef,
  findContinuingOutputs,
  getContinuingOutputs,

  -- * Validator functions
  pubKeyOutputsAt,
  valuePaidTo,
  spendsOutput,
  txSignedBy,
  valueSpent,
  valueProduced,
  ownCurrencySymbol,
) where

import GHC.Generics (Generic)
import PlutusTx
import PlutusTx.AsData qualified as PlutusTx
import PlutusTx.Data.List (List)
import PlutusTx.Data.List qualified as Data.List
import PlutusTx.Prelude
import Prettyprinter
import Prettyprinter.Extras

import PlutusLedgerApi.V1.Crypto (PubKeyHash (..))
import PlutusLedgerApi.V1.Data.Address (pattern Address)
import PlutusLedgerApi.V1.Data.Credential (StakingCredential, pattern PubKeyCredential)
import PlutusLedgerApi.V1.Data.DCert (DCert)
import PlutusLedgerApi.V1.Data.Time (POSIXTimeRange)
import PlutusLedgerApi.V1.Data.Tx (TxId (..), TxOut, TxOutRef, pattern TxOut, pattern TxOutRef,
                                   txOutAddress, txOutDatumHash, txOutRefId, txOutRefIdx,
                                   txOutValue)
import PlutusLedgerApi.V1.Data.Value (CurrencySymbol (..), Value)
import PlutusLedgerApi.V1.Scripts
import Prelude qualified as Haskell

{- Note [Script types in pending transactions]
To validate a transaction, we have to evaluate the validation script of each of
the transaction's inputs. The validation script sees the data of the
transaction output it validates, and the redeemer of the transaction input of
the transaction that consumes it.
In addition, the validation script also needs information on the transaction as
a whole (not just the output-input pair it is concerned with). This information
is provided by the `TxInfo` type. A `TxInfo` contains the hashes of
redeemer and data scripts of all of its inputs and outputs.
-}

-- | An input of a pending transaction.
PlutusTx.asData
  [d|
    data TxInInfo = TxInInfo
      { txInInfoOutRef   :: TxOutRef
      , txInInfoResolved :: TxOut
      }
      deriving stock (Generic, Haskell.Show, Haskell.Eq)
      deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
  |]

makeLift ''TxInInfo

instance Eq TxInInfo where
  TxInInfo TxOutRef
ref TxOut
res == :: TxInInfo -> TxInInfo -> Bool
== TxInInfo TxOutRef
ref' TxOut
res' = TxOutRef
ref TxOutRef -> TxOutRef -> Bool
forall a. Eq a => a -> a -> Bool
== TxOutRef
ref' Bool -> Bool -> Bool
&& TxOut
res TxOut -> TxOut -> Bool
forall a. Eq a => a -> a -> Bool
== TxOut
res'

instance Pretty TxInInfo where
  pretty :: forall ann. TxInInfo -> Doc ann
pretty TxInInfo{TxOutRef
txInInfoOutRef :: TxInInfo -> TxOutRef
txInInfoOutRef :: TxOutRef
txInInfoOutRef, TxOut
txInInfoResolved :: TxInInfo -> TxOut
txInInfoResolved :: TxOut
txInInfoResolved} =
    TxOutRef -> Doc ann
forall ann. TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOutRef
txInInfoOutRef Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
"->" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxOut -> Doc ann
forall ann. TxOut -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOut
txInInfoResolved

-- | Purpose of the script that is currently running
PlutusTx.asData
  [d|
    data ScriptPurpose
      = Minting CurrencySymbol
      | Spending TxOutRef
      | Rewarding StakingCredential
      | Certifying DCert
      deriving stock (Generic, Haskell.Show, Haskell.Eq)
      deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
      deriving Pretty via (PrettyShow ScriptPurpose)
  |]

makeLift ''ScriptPurpose

instance Eq ScriptPurpose where
  {-# INLINEABLE (==) #-}
  Minting CurrencySymbol
cs == :: ScriptPurpose -> ScriptPurpose -> Bool
== Minting CurrencySymbol
cs'           = CurrencySymbol
cs CurrencySymbol -> CurrencySymbol -> Bool
forall a. Eq a => a -> a -> Bool
== CurrencySymbol
cs'
  Spending TxOutRef
ref == Spending TxOutRef
ref'       = TxOutRef
ref TxOutRef -> TxOutRef -> Bool
forall a. Eq a => a -> a -> Bool
== TxOutRef
ref'
  Rewarding StakingCredential
sc == Rewarding StakingCredential
sc'       = StakingCredential
sc StakingCredential -> StakingCredential -> Bool
forall a. Eq a => a -> a -> Bool
== StakingCredential
sc'
  Certifying DCert
cert == Certifying DCert
cert' = DCert
cert DCert -> DCert -> Bool
forall a. Eq a => a -> a -> Bool
== DCert
cert'
  ScriptPurpose
_ == ScriptPurpose
_                              = Bool
False

{-| A pending transaction. This is the view as seen by validator scripts,
so some details are stripped out.
-}
PlutusTx.asData
  [d|
    data TxInfo = TxInfo
      { txInfoInputs      :: List TxInInfo
      -- ^ Transaction inputs; cannot be an empty list
      , txInfoOutputs     :: List TxOut
      -- ^ Transaction outputs
      , txInfoFee         :: Value
      -- ^ The fee paid by this transaction.
      , txInfoMint        :: Value
      -- ^ The 'Value' minted by this transaction.
      , txInfoDCert       :: List DCert
      -- ^ Digests of certificates included in this transaction
      -- TODO: is this a map? is this a list?
      , txInfoWdrl        :: List (StakingCredential, Integer)
      -- ^ Withdrawals
      , txInfoValidRange  :: POSIXTimeRange
      -- ^ The valid range for the transaction.
      , txInfoSignatories :: List PubKeyHash
      -- ^ Signatures provided with the transaction, attested that they all signed the tx
      -- TODO: is this a map? is this a list?
      , txInfoData        :: List (DatumHash, Datum)
      -- ^ The lookup table of datums attached to the transaction
      , txInfoId          :: TxId
      -- ^ Hash of the pending transaction body (i.e. transaction excluding witnesses)
      }
      deriving stock (Generic, Haskell.Show, Haskell.Eq)
      deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
  |]

makeLift ''TxInfo

instance Eq TxInfo where
  {-# INLINEABLE (==) #-}
  TxInfo List TxInInfo
i List TxOut
o Value
f Value
m List DCert
c List (StakingCredential, Integer)
w POSIXTimeRange
r List PubKeyHash
s List (DatumHash, Datum)
d TxId
tid == :: TxInfo -> TxInfo -> Bool
== TxInfo List TxInInfo
i' List TxOut
o' Value
f' Value
m' List DCert
c' List (StakingCredential, Integer)
w' POSIXTimeRange
r' List PubKeyHash
s' List (DatumHash, Datum)
d' TxId
tid' =
    List TxInInfo
i
      List TxInInfo -> List TxInInfo -> Bool
forall a. Eq a => a -> a -> Bool
== List TxInInfo
i'
      Bool -> Bool -> Bool
&& List TxOut
o
      List TxOut -> List TxOut -> Bool
forall a. Eq a => a -> a -> Bool
== List TxOut
o'
      Bool -> Bool -> Bool
&& Value
f
      Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
== Value
f'
      Bool -> Bool -> Bool
&& Value
m
      Value -> Value -> Bool
forall a. Eq a => a -> a -> Bool
== Value
m'
      Bool -> Bool -> Bool
&& List DCert
c
      List DCert -> List DCert -> Bool
forall a. Eq a => a -> a -> Bool
== List DCert
c'
      Bool -> Bool -> Bool
&& List (StakingCredential, Integer)
w
      List (StakingCredential, Integer)
-> List (StakingCredential, Integer) -> Bool
forall a. Eq a => a -> a -> Bool
== List (StakingCredential, Integer)
w'
      Bool -> Bool -> Bool
&& POSIXTimeRange
r
      POSIXTimeRange -> POSIXTimeRange -> Bool
forall a. Eq a => a -> a -> Bool
== POSIXTimeRange
r'
      Bool -> Bool -> Bool
&& List PubKeyHash
s
      List PubKeyHash -> List PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
== List PubKeyHash
s'
      Bool -> Bool -> Bool
&& List (DatumHash, Datum)
d
      List (DatumHash, Datum) -> List (DatumHash, Datum) -> Bool
forall a. Eq a => a -> a -> Bool
== List (DatumHash, Datum)
d'
      Bool -> Bool -> Bool
&& TxId
tid
      TxId -> TxId -> Bool
forall a. Eq a => a -> a -> Bool
== TxId
tid'

instance Pretty TxInfo where
  pretty :: forall ann. TxInfo -> Doc ann
pretty
    TxInfo
      { List TxInInfo
txInfoInputs :: TxInfo -> List TxInInfo
txInfoInputs :: List TxInInfo
txInfoInputs
      , List TxOut
txInfoOutputs :: TxInfo -> List TxOut
txInfoOutputs :: List TxOut
txInfoOutputs
      , Value
txInfoFee :: TxInfo -> Value
txInfoFee :: Value
txInfoFee
      , Value
txInfoMint :: TxInfo -> Value
txInfoMint :: Value
txInfoMint
      , List DCert
txInfoDCert :: TxInfo -> List DCert
txInfoDCert :: List DCert
txInfoDCert
      , List (StakingCredential, Integer)
txInfoWdrl :: TxInfo -> List (StakingCredential, Integer)
txInfoWdrl :: List (StakingCredential, Integer)
txInfoWdrl
      , POSIXTimeRange
txInfoValidRange :: TxInfo -> POSIXTimeRange
txInfoValidRange :: POSIXTimeRange
txInfoValidRange
      , List PubKeyHash
txInfoSignatories :: TxInfo -> List PubKeyHash
txInfoSignatories :: List PubKeyHash
txInfoSignatories
      , List (DatumHash, Datum)
txInfoData :: TxInfo -> List (DatumHash, Datum)
txInfoData :: List (DatumHash, Datum)
txInfoData
      , TxId
txInfoId :: TxInfo -> TxId
txInfoId :: TxId
txInfoId
      } =
      [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
        [ Doc ann
"TxId:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxId -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. TxId -> Doc ann
pretty TxId
txInfoId
        , Doc ann
"Inputs:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> List TxInInfo -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. List TxInInfo -> Doc ann
pretty List TxInInfo
txInfoInputs
        , Doc ann
"Outputs:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> List TxOut -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. List TxOut -> Doc ann
pretty List TxOut
txInfoOutputs
        , Doc ann
"Fee:" 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
forall ann. Value -> Doc ann
pretty Value
txInfoFee
        , Doc ann
"Value minted:" 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
forall ann. Value -> Doc ann
pretty Value
txInfoMint
        , Doc ann
"DCerts:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> List DCert -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. List DCert -> Doc ann
pretty List DCert
txInfoDCert
        , Doc ann
"Wdrl:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> List (StakingCredential, Integer) -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. List (StakingCredential, Integer) -> Doc ann
pretty List (StakingCredential, Integer)
txInfoWdrl
        , Doc ann
"Valid range:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> POSIXTimeRange -> Doc ann
forall ann. POSIXTimeRange -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty POSIXTimeRange
txInfoValidRange
        , Doc ann
"Signatories:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> List PubKeyHash -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. List PubKeyHash -> Doc ann
pretty List PubKeyHash
txInfoSignatories
        , Doc ann
"Datums:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> List (DatumHash, Datum) -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. List (DatumHash, Datum) -> Doc ann
pretty List (DatumHash, Datum)
txInfoData
        ]

-- | The context that the currently-executing script can access.
PlutusTx.asData
  [d|
    data ScriptContext = ScriptContext
      { scriptContextTxInfo  :: TxInfo
      -- ^ information about the transaction the currently-executing script is included in
      , scriptContextPurpose :: ScriptPurpose
      -- ^ the purpose of the currently-executing script
      }
      deriving stock (Generic, Haskell.Eq, Haskell.Show)
      deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
  |]

makeLift ''ScriptContext

instance Eq ScriptContext where
  {-# INLINEABLE (==) #-}
  ScriptContext TxInfo
info ScriptPurpose
purpose == :: ScriptContext -> ScriptContext -> Bool
== ScriptContext TxInfo
info' ScriptPurpose
purpose' = TxInfo
info TxInfo -> TxInfo -> Bool
forall a. Eq a => a -> a -> Bool
== TxInfo
info' Bool -> Bool -> Bool
&& ScriptPurpose
purpose ScriptPurpose -> ScriptPurpose -> Bool
forall a. Eq a => a -> a -> Bool
== ScriptPurpose
purpose'

instance Pretty ScriptContext where
  pretty :: forall ann. ScriptContext -> Doc ann
pretty ScriptContext{TxInfo
scriptContextTxInfo :: ScriptContext -> TxInfo
scriptContextTxInfo :: TxInfo
scriptContextTxInfo, ScriptPurpose
scriptContextPurpose :: ScriptContext -> ScriptPurpose
scriptContextPurpose :: ScriptPurpose
scriptContextPurpose} =
    [Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
      [ Doc ann
"Purpose:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> ScriptPurpose -> Doc ann
forall ann. ScriptPurpose -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ScriptPurpose
scriptContextPurpose
      , Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
nest 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
"TxInfo:", TxInfo -> Doc ann
forall ann. TxInfo -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxInfo
scriptContextTxInfo]
      ]

-- | Find the input currently being validated.
findOwnInput :: ScriptContext -> Maybe TxInInfo
findOwnInput :: ScriptContext -> Maybe TxInInfo
findOwnInput
  ScriptContext
    { scriptContextTxInfo :: ScriptContext -> TxInfo
scriptContextTxInfo = TxInfo{List TxInInfo
txInfoInputs :: TxInfo -> List TxInInfo
txInfoInputs :: List TxInInfo
txInfoInputs}
    , scriptContextPurpose :: ScriptContext -> ScriptPurpose
scriptContextPurpose = Spending TxOutRef
txOutRef
    } =
    (TxInInfo -> Bool) -> List TxInInfo -> Maybe TxInInfo
forall a. UnsafeFromData a => (a -> Bool) -> List a -> Maybe a
Data.List.find
      (\TxInInfo{TxOutRef
txInInfoOutRef :: TxInInfo -> TxOutRef
txInInfoOutRef :: TxOutRef
txInInfoOutRef} -> TxOutRef
txInInfoOutRef TxOutRef -> TxOutRef -> Bool
forall a. Eq a => a -> a -> Bool
== TxOutRef
txOutRef)
      List TxInInfo
txInfoInputs
findOwnInput ScriptContext
_ = Maybe TxInInfo
forall a. Maybe a
Nothing
{-# INLINEABLE findOwnInput #-}

-- | Find the data corresponding to a data hash, if there is one
findDatum :: DatumHash -> TxInfo -> Maybe Datum
findDatum :: DatumHash -> TxInfo -> Maybe Datum
findDatum DatumHash
dsh TxInfo{List (DatumHash, Datum)
txInfoData :: TxInfo -> List (DatumHash, Datum)
txInfoData :: List (DatumHash, Datum)
txInfoData} =
  (DatumHash, Datum) -> Datum
forall a b. (a, b) -> b
snd ((DatumHash, Datum) -> Datum)
-> Maybe (DatumHash, Datum) -> Maybe Datum
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((DatumHash, Datum) -> Bool)
-> List (DatumHash, Datum) -> Maybe (DatumHash, Datum)
forall a. UnsafeFromData a => (a -> Bool) -> List a -> Maybe a
Data.List.find (DatumHash, Datum) -> Bool
forall {b}. (DatumHash, b) -> Bool
f List (DatumHash, Datum)
txInfoData
 where
  f :: (DatumHash, b) -> Bool
f (DatumHash
dsh', b
_) = DatumHash
dsh' DatumHash -> DatumHash -> Bool
forall a. Eq a => a -> a -> Bool
== DatumHash
dsh
{-# INLINEABLE findDatum #-}

{-| Find the hash of a datum, if it is part of the pending transaction's
  hashes
-}
findDatumHash :: Datum -> TxInfo -> Maybe DatumHash
findDatumHash :: Datum -> TxInfo -> Maybe DatumHash
findDatumHash Datum
ds TxInfo{List (DatumHash, Datum)
txInfoData :: TxInfo -> List (DatumHash, Datum)
txInfoData :: List (DatumHash, Datum)
txInfoData} =
  (DatumHash, Datum) -> DatumHash
forall a b. (a, b) -> a
fst ((DatumHash, Datum) -> DatumHash)
-> Maybe (DatumHash, Datum) -> Maybe DatumHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ((DatumHash, Datum) -> Bool)
-> List (DatumHash, Datum) -> Maybe (DatumHash, Datum)
forall a. UnsafeFromData a => (a -> Bool) -> List a -> Maybe a
Data.List.find (DatumHash, Datum) -> Bool
forall {a}. (a, Datum) -> Bool
f List (DatumHash, Datum)
txInfoData
 where
  f :: (a, Datum) -> Bool
f (a
_, Datum
ds') = Datum
ds' Datum -> Datum -> Bool
forall a. Eq a => a -> a -> Bool
== Datum
ds
{-# INLINEABLE findDatumHash #-}

{-| Given a UTXO reference and a transaction (`TxInfo`), resolve it to one of
the transaction's inputs (`TxInInfo`).
-}
findTxInByTxOutRef :: TxOutRef -> TxInfo -> Maybe TxInInfo
findTxInByTxOutRef :: TxOutRef -> TxInfo -> Maybe TxInInfo
findTxInByTxOutRef TxOutRef
outRef TxInfo{List TxInInfo
txInfoInputs :: TxInfo -> List TxInInfo
txInfoInputs :: List TxInInfo
txInfoInputs} =
  (TxInInfo -> Bool) -> List TxInInfo -> Maybe TxInInfo
forall a. UnsafeFromData a => (a -> Bool) -> List a -> Maybe a
Data.List.find
    (\TxInInfo{TxOutRef
txInInfoOutRef :: TxInInfo -> TxOutRef
txInInfoOutRef :: TxOutRef
txInInfoOutRef} -> TxOutRef
txInInfoOutRef TxOutRef -> TxOutRef -> Bool
forall a. Eq a => a -> a -> Bool
== TxOutRef
outRef)
    List TxInInfo
txInfoInputs
{-# INLINEABLE findTxInByTxOutRef #-}

{-| Finds all the outputs that pay to the same script address that we are
currently spending from, if any.
-}
findContinuingOutputs :: ScriptContext -> List Integer
findContinuingOutputs :: ScriptContext -> List Integer
findContinuingOutputs ScriptContext
ctx
  | Just
      TxInInfo
        { txInInfoResolved :: TxInInfo -> TxOut
txInInfoResolved = TxOut{Address
txOutAddress :: TxOut -> Address
txOutAddress :: Address
txOutAddress}
        } <-
      ScriptContext -> Maybe TxInInfo
findOwnInput ScriptContext
ctx =
      (TxOut -> Bool) -> List TxOut -> List Integer
forall a. UnsafeFromData a => (a -> Bool) -> List a -> List Integer
Data.List.findIndices
        (Address -> TxOut -> Bool
f Address
txOutAddress)
        (TxInfo -> List TxOut
txInfoOutputs (TxInfo -> List TxOut) -> TxInfo -> List TxOut
forall a b. (a -> b) -> a -> b
$ ScriptContext -> TxInfo
scriptContextTxInfo ScriptContext
ctx)
 where
  f :: Address -> TxOut -> Bool
f Address
addr TxOut{txOutAddress :: TxOut -> Address
txOutAddress = Address
otherAddress} =
    Address
addr Address -> Address -> Bool
forall a. Eq a => a -> a -> Bool
== Address
otherAddress
findContinuingOutputs ScriptContext
_ =
  BuiltinString -> List Integer
forall a. BuiltinString -> a
traceError BuiltinString
"Le" -- "Can't find any continuing outputs"
{-# INLINEABLE findContinuingOutputs #-}

{-| Get all the outputs that pay to the same script address we are currently
spending from, if any.
-}
getContinuingOutputs :: ScriptContext -> List TxOut
getContinuingOutputs :: ScriptContext -> List TxOut
getContinuingOutputs ScriptContext
ctx
  | Just
      TxInInfo
        { txInInfoResolved :: TxInInfo -> TxOut
txInInfoResolved = TxOut{Address
txOutAddress :: TxOut -> Address
txOutAddress :: Address
txOutAddress}
        } <-
      ScriptContext -> Maybe TxInInfo
findOwnInput ScriptContext
ctx =
      (TxOut -> Bool) -> List TxOut -> List TxOut
forall a.
(UnsafeFromData a, ToData a) =>
(a -> Bool) -> List a -> List a
Data.List.filter
        (Address -> TxOut -> Bool
f Address
txOutAddress)
        (TxInfo -> List TxOut
txInfoOutputs (TxInfo -> List TxOut) -> TxInfo -> List TxOut
forall a b. (a -> b) -> a -> b
$ ScriptContext -> TxInfo
scriptContextTxInfo ScriptContext
ctx)
 where
  f :: Address -> TxOut -> Bool
f Address
addr TxOut{txOutAddress :: TxOut -> Address
txOutAddress = Address
otherAddress} =
    Address
addr Address -> Address -> Bool
forall a. Eq a => a -> a -> Bool
== Address
otherAddress
getContinuingOutputs ScriptContext
_ =
  BuiltinString -> List TxOut
forall a. BuiltinString -> a
traceError BuiltinString
"Lf" -- "Can't get any continuing outputs"
{-# INLINEABLE getContinuingOutputs #-}

{- Note [Hashes in validator scripts]

We need to deal with hashes of four different things in a validator script:

1. Transactions
2. Validator scripts
3. Data scripts
4. Redeemer scripts

The mockchain code in 'Ledger.Tx' only deals with the hashes of(1)
and (2), and uses the 'Ledger.Tx.TxId' and `Digest SHA256` types for
them.

In PLC validator scripts the situation is different: First, they need to work
with hashes of (1-4). Second, the `Digest SHA256` type is not available in PLC
- we have to represent all hashes as `ByteStrings`.

To ensure that we only compare hashes of the correct type inside a validator
script, we define a newtype for each of them, as well as functions for creating
them from the correct types in Haskell, and for comparing them (in
`Language.Plutus.Runtime.TH`).

-}

-- | Check if a transaction was signed by the given public key.
txSignedBy :: TxInfo -> PubKeyHash -> Bool
txSignedBy :: TxInfo -> PubKeyHash -> Bool
txSignedBy TxInfo{List PubKeyHash
txInfoSignatories :: TxInfo -> List PubKeyHash
txInfoSignatories :: List PubKeyHash
txInfoSignatories} PubKeyHash
k =
  case (PubKeyHash -> Bool) -> List PubKeyHash -> Maybe PubKeyHash
forall a. UnsafeFromData a => (a -> Bool) -> List a -> Maybe a
Data.List.find (PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
(==) PubKeyHash
k) List PubKeyHash
txInfoSignatories of
    Just PubKeyHash
_  -> Bool
True
    Maybe PubKeyHash
Nothing -> Bool
False
{-# INLINEABLE txSignedBy #-}

-- | Get the values paid to a public key address by a pending transaction.
pubKeyOutputsAt :: PubKeyHash -> TxInfo -> List Value
pubKeyOutputsAt :: PubKeyHash -> TxInfo -> List Value
pubKeyOutputsAt PubKeyHash
pk TxInfo
p =
  let flt :: TxOut -> Maybe Value
flt
        TxOut
          { txOutAddress :: TxOut -> Address
txOutAddress = Address (PubKeyCredential PubKeyHash
pk') Maybe StakingCredential
_
          , Value
txOutValue :: TxOut -> Value
txOutValue :: Value
txOutValue
          } | PubKeyHash
pk PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
== PubKeyHash
pk' = Value -> Maybe Value
forall a. a -> Maybe a
Just Value
txOutValue
      flt TxOut
_ = Maybe Value
forall a. Maybe a
Nothing
   in (TxOut -> Maybe Value) -> List TxOut -> List Value
forall a b.
(UnsafeFromData a, ToData b) =>
(a -> Maybe b) -> List a -> List b
Data.List.mapMaybe TxOut -> Maybe Value
flt (TxInfo -> List TxOut
txInfoOutputs TxInfo
p)
{-# INLINEABLE pubKeyOutputsAt #-}

-- | Get the total value paid to a public key address by a pending transaction.
valuePaidTo :: TxInfo -> PubKeyHash -> Value
valuePaidTo :: TxInfo -> PubKeyHash -> Value
valuePaidTo TxInfo
ptx PubKeyHash
pkh = List Value -> Value
forall a. (Monoid a, UnsafeFromData a) => List a -> a
Data.List.mconcat (PubKeyHash -> TxInfo -> List Value
pubKeyOutputsAt PubKeyHash
pkh TxInfo
ptx)
{-# INLINEABLE valuePaidTo #-}

-- | Get the total value of inputs spent by this transaction.
valueSpent :: TxInfo -> Value
valueSpent :: TxInfo -> Value
valueSpent = (TxInInfo -> Value) -> List TxInInfo -> Value
forall a m. (UnsafeFromData a, Monoid m) => (a -> m) -> List a -> m
Data.List.foldMap (TxOut -> Value
txOutValue (TxOut -> Value) -> (TxInInfo -> TxOut) -> TxInInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxInInfo -> TxOut
txInInfoResolved) (List TxInInfo -> Value)
-> (TxInfo -> List TxInInfo) -> TxInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxInfo -> List TxInInfo
txInfoInputs
{-# INLINEABLE valueSpent #-}

-- | Get the total value of outputs produced by this transaction.
valueProduced :: TxInfo -> Value
valueProduced :: TxInfo -> Value
valueProduced = (TxOut -> Value) -> List TxOut -> Value
forall a m. (UnsafeFromData a, Monoid m) => (a -> m) -> List a -> m
Data.List.foldMap TxOut -> Value
txOutValue (List TxOut -> Value) -> (TxInfo -> List TxOut) -> TxInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TxInfo -> List TxOut
txInfoOutputs
{-# INLINEABLE valueProduced #-}

-- | The 'CurrencySymbol' of the current validator script.
ownCurrencySymbol :: ScriptContext -> CurrencySymbol
ownCurrencySymbol :: ScriptContext -> CurrencySymbol
ownCurrencySymbol ScriptContext{scriptContextPurpose :: ScriptContext -> ScriptPurpose
scriptContextPurpose = Minting CurrencySymbol
cs} = CurrencySymbol
cs
ownCurrencySymbol ScriptContext
_ =
  BuiltinString -> CurrencySymbol
forall a. BuiltinString -> a
traceError BuiltinString
"Lh" -- "Can't get currency symbol of the current validator script"
{-# INLINEABLE ownCurrencySymbol #-}

{-| Check if the pending transaction spends a specific transaction output
(identified by the hash of a transaction and an index into that
transactions' outputs)
-}
spendsOutput :: TxInfo -> TxId -> Integer -> Bool
spendsOutput :: TxInfo -> TxId -> Integer -> Bool
spendsOutput TxInfo
p TxId
h Integer
i =
  let spendsOutRef :: TxInInfo -> Bool
spendsOutRef TxInInfo
inp =
        let outRef :: TxOutRef
outRef = TxInInfo -> TxOutRef
txInInfoOutRef TxInInfo
inp
         in TxId
h
              TxId -> TxId -> Bool
forall a. Eq a => a -> a -> Bool
== TxOutRef -> TxId
txOutRefId TxOutRef
outRef
              Bool -> Bool -> Bool
&& Integer
i
              Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== TxOutRef -> Integer
txOutRefIdx TxOutRef
outRef
   in (TxInInfo -> Bool) -> List TxInInfo -> Bool
forall a. UnsafeFromData a => (a -> Bool) -> List a -> Bool
Data.List.any TxInInfo -> Bool
spendsOutRef (TxInfo -> List TxInInfo
txInfoInputs TxInfo
p)
{-# INLINEABLE spendsOutput #-}