{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RoleAnnotations #-}
{-# OPTIONS_GHC -Wno-orphans #-}

{- | = Note

The 'Value.PValue', 'AssocMap.PMap' and 'Interval.PInterval'-related
functionality can be found in other modules, as these clash with the
Plutarch prelude. These should be imported qualified.
-}
module Plutarch.LedgerApi.V3 (
  -- * Contexts
  Contexts.PScriptContext (..),
  Contexts.PTxInfo (..),
  Contexts.PScriptInfo (..),
  Contexts.PScriptPurpose (..),

  -- * Tx

  -- ** Types
  V3Tx.PTxOutRef (..),
  V2Tx.PTxOut (..),
  V3Tx.PTxId (..),
  Contexts.PTxInInfo (..),
  V2Tx.POutputDatum (..),

  -- ** Functions
  pgetContinuingOutputs,
  pfindOwnInput,

  -- * Script

  -- ** Types
  Scripts.PDatum (..),
  Scripts.PDatumHash (..),
  Scripts.PRedeemer (..),
  Scripts.PRedeemerHash (..),
  Scripts.PScriptHash (..),

  -- ** Functions
  scriptHash,
  datumHash,
  redeemerHash,
  dataHash,
  pparseDatum,

  -- * Value
  Value.PValue (..),
  Value.AmountGuarantees (..),
  Value.PCurrencySymbol (..),
  Value.PTokenName (..),
  Value.PLovelace (..),

  -- * Assoc map

  -- ** Types
  AssocMap.PMap (..),
  AssocMap.KeyGuarantees (..),
  AssocMap.Commutativity (..),

  -- * Address
  Credential.PCredential (..),
  Credential.PStakingCredential (..),
  Address.PAddress (..),

  -- * Time
  Time.PPosixTime (..),
  Time.pposixTime,
  Time.unPPosixTime,

  -- * Interval
  Interval.PInterval (..),
  Interval.PLowerBound (..),
  Interval.PUpperBound (..),
  Interval.PExtended (..),

  -- * CIP-1694
  Contexts.PTxCert (..),
  Contexts.PDelegatee (..),
  Contexts.PDRepCredential (..),
  Contexts.PColdCommitteeCredential (..),
  Contexts.PHotCommitteeCredential (..),
  Contexts.PDRep (..),
  Contexts.PVoter (..),
  Contexts.PGovernanceActionId (..),
  Contexts.PVote (..),
  Contexts.PProtocolVersion (..),
  Contexts.PProposalProcedure (..),
  Contexts.PGovernanceAction (..),
  Contexts.PChangedParameters (..),
  Contexts.PConstitution (..),
  Contexts.PCommittee (..),

  -- * Crypto

  -- ** Types
  PubKey (..),
  Crypto.PPubKeyHash (..),
  pubKeyHash,

  -- * Utilities

  -- ** Types
  Utils.PMaybeData (..),
  Utils.PRationalData (..),

  -- ** Utilities
  Utils.pfromDJust,
  Utils.pisDJust,
  Utils.pmaybeData,
  Utils.pdjust,
  Utils.pdnothing,
  Utils.pmaybeToMaybeData,
  Utils.passertPDJust,
  Utils.prationalFromData,
) where

import Codec.Serialise (serialise)
import Crypto.Hash (
  Blake2b_224 (Blake2b_224),
  Blake2b_256 (Blake2b_256),
  hashWith,
 )
import Data.ByteArray (convert)
import Data.ByteString (ByteString, toStrict)
import Data.ByteString.Short (fromShort)
import Data.Coerce (coerce)
import Data.Kind (Type)
import Plutarch.LedgerApi.AssocMap qualified as AssocMap
import Plutarch.LedgerApi.Interval qualified as Interval
import Plutarch.LedgerApi.Utils qualified as Utils
import Plutarch.LedgerApi.V1.Address qualified as Address
import Plutarch.LedgerApi.V1.Credential qualified as Credential
import Plutarch.LedgerApi.V1.Crypto qualified as Crypto
import Plutarch.LedgerApi.V1.Scripts qualified as Scripts
import Plutarch.LedgerApi.V1.Time qualified as Time
import Plutarch.LedgerApi.V2.Tx qualified as V2Tx
import Plutarch.LedgerApi.V3.Contexts qualified as Contexts
import Plutarch.LedgerApi.V3.Tx qualified as V3Tx
import Plutarch.LedgerApi.Value qualified as Value
import Plutarch.Prelude
import Plutarch.Script (Script (unScript))
import PlutusLedgerApi.Common (serialiseUPLC)
import PlutusLedgerApi.V3 qualified as Plutus
import PlutusTx.Prelude qualified as PlutusTx

{- | Hash a script, appending the Plutus V2 prefix.

@since 2.0.0
-}
scriptHash :: Script -> Plutus.ScriptHash
scriptHash :: Script -> ScriptHash
scriptHash = ByteString -> Script -> ScriptHash
hashScriptWithPrefix ByteString
"\x02"

-- | @since 2.0.0
newtype PubKey = PubKey
  { PubKey -> LedgerBytes
getPubKey :: Plutus.LedgerBytes
  -- ^ @since 2.0.0
  }
  deriving stock
    ( -- | @since 2.0.0
      PubKey -> PubKey -> Bool
(PubKey -> PubKey -> Bool)
-> (PubKey -> PubKey -> Bool) -> Eq PubKey
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: PubKey -> PubKey -> Bool
== :: PubKey -> PubKey -> Bool
$c/= :: PubKey -> PubKey -> Bool
/= :: PubKey -> PubKey -> Bool
Eq
    , -- | @since 2.0.0
      Eq PubKey
Eq PubKey =>
(PubKey -> PubKey -> Ordering)
-> (PubKey -> PubKey -> Bool)
-> (PubKey -> PubKey -> Bool)
-> (PubKey -> PubKey -> Bool)
-> (PubKey -> PubKey -> Bool)
-> (PubKey -> PubKey -> PubKey)
-> (PubKey -> PubKey -> PubKey)
-> Ord PubKey
PubKey -> PubKey -> Bool
PubKey -> PubKey -> Ordering
PubKey -> PubKey -> PubKey
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: PubKey -> PubKey -> Ordering
compare :: PubKey -> PubKey -> Ordering
$c< :: PubKey -> PubKey -> Bool
< :: PubKey -> PubKey -> Bool
$c<= :: PubKey -> PubKey -> Bool
<= :: PubKey -> PubKey -> Bool
$c> :: PubKey -> PubKey -> Bool
> :: PubKey -> PubKey -> Bool
$c>= :: PubKey -> PubKey -> Bool
>= :: PubKey -> PubKey -> Bool
$cmax :: PubKey -> PubKey -> PubKey
max :: PubKey -> PubKey -> PubKey
$cmin :: PubKey -> PubKey -> PubKey
min :: PubKey -> PubKey -> PubKey
Ord
    )
  deriving stock
    ( -- | @since 2.0.0
      Int -> PubKey -> ShowS
[PubKey] -> ShowS
PubKey -> String
(Int -> PubKey -> ShowS)
-> (PubKey -> String) -> ([PubKey] -> ShowS) -> Show PubKey
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> PubKey -> ShowS
showsPrec :: Int -> PubKey -> ShowS
$cshow :: PubKey -> String
show :: PubKey -> String
$cshowList :: [PubKey] -> ShowS
showList :: [PubKey] -> ShowS
Show
    )

-- | @since 2.0.0
pubKeyHash :: PubKey -> Plutus.PubKeyHash
pubKeyHash :: PubKey -> PubKeyHash
pubKeyHash = (LedgerBytes -> BuiltinByteString) -> PubKey -> PubKeyHash
forall a b. Coercible a b => a -> b
coerce LedgerBytes -> BuiltinByteString
hashLedgerBytes

-- | @since 2.0.0
datumHash :: Plutus.Datum -> Plutus.DatumHash
datumHash :: Datum -> DatumHash
datumHash = BuiltinByteString -> DatumHash
forall a b. Coercible a b => a -> b
coerce (BuiltinByteString -> DatumHash)
-> (Datum -> BuiltinByteString) -> Datum -> DatumHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Datum -> BuiltinByteString
forall a. ToData a => a -> BuiltinByteString
dataHash

-- | @since 2.0.0
dataHash ::
  forall (a :: Type).
  Plutus.ToData a =>
  a ->
  PlutusTx.BuiltinByteString
dataHash :: forall a. ToData a => a -> BuiltinByteString
dataHash = Data -> BuiltinByteString
hashData (Data -> BuiltinByteString)
-> (a -> Data) -> a -> BuiltinByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Data
forall a. ToData a => a -> Data
Plutus.toData

-- | @since 2.0.0
redeemerHash :: Plutus.Redeemer -> Plutus.RedeemerHash
redeemerHash :: Redeemer -> RedeemerHash
redeemerHash = BuiltinByteString -> RedeemerHash
forall a b. Coercible a b => a -> b
coerce (BuiltinByteString -> RedeemerHash)
-> (Redeemer -> BuiltinByteString) -> Redeemer -> RedeemerHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Redeemer -> BuiltinByteString
forall a. ToData a => a -> BuiltinByteString
dataHash

{- | Find the output txns corresponding to the input being validated.

  Takes as arguments the inputs, outputs and the spending transaction referenced
  from `PScriptPurpose`.

  __Example:__

  @
  ctx <- tcont $ pletFields @["txInfo", "purpose"] sc
  pmatchC (getField @"purpose" ctx) >>= \case
    PSpending outRef' -> do
      let outRef = pfield @"_0" # outRef'
          inputs = pfield @"inputs" # (getField @"txInfo" ctx)
          outputs = pfield @"outputs" # (getField @"txInfo" ctx)
      pure $ pgetContinuingOutputs # inputs # outputs # outRef
    _ ->
      pure $ ptraceInfoError "not a spending tx"
  @

  @since 2.1.0
-}
pgetContinuingOutputs ::
  forall (s :: S).
  Term
    s
    ( PBuiltinList Contexts.PTxInInfo
        :--> PBuiltinList V2Tx.PTxOut
        :--> V3Tx.PTxOutRef
        :--> PBuiltinList V2Tx.PTxOut
    )
pgetContinuingOutputs :: forall (s :: S).
Term
  s
  (PBuiltinList PTxInInfo
   :--> (PBuiltinList PTxOut
         :--> (PTxOutRef :--> PBuiltinList PTxOut)))
pgetContinuingOutputs = (forall (s :: S).
 Term
   s
   (PBuiltinList PTxInInfo
    :--> (PBuiltinList PTxOut
          :--> (PTxOutRef :--> PBuiltinList PTxOut))))
-> Term
     s
     (PBuiltinList PTxInInfo
      :--> (PBuiltinList PTxOut
            :--> (PTxOutRef :--> PBuiltinList PTxOut)))
forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic ((forall (s :: S).
  Term
    s
    (PBuiltinList PTxInInfo
     :--> (PBuiltinList PTxOut
           :--> (PTxOutRef :--> PBuiltinList PTxOut))))
 -> Term
      s
      (PBuiltinList PTxInInfo
       :--> (PBuiltinList PTxOut
             :--> (PTxOutRef :--> PBuiltinList PTxOut))))
-> (forall (s :: S).
    Term
      s
      (PBuiltinList PTxInInfo
       :--> (PBuiltinList PTxOut
             :--> (PTxOutRef :--> PBuiltinList PTxOut))))
-> Term
     s
     (PBuiltinList PTxInInfo
      :--> (PBuiltinList PTxOut
            :--> (PTxOutRef :--> PBuiltinList PTxOut)))
forall a b. (a -> b) -> a -> b
$
  (Term s (PBuiltinList PTxInInfo)
 -> Term s (PBuiltinList PTxOut)
 -> Term s PTxOutRef
 -> Term s (PBuiltinList PTxOut))
-> Term
     s
     (PBuiltinList PTxInInfo
      :--> (PBuiltinList PTxOut
            :--> (PTxOutRef :--> PBuiltinList PTxOut)))
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: PType).
HasCallStack =>
(Term s c
 -> Term s (PBuiltinList PTxOut)
 -> Term s PTxOutRef
 -> Term s (PBuiltinList PTxOut))
-> Term
     s
     (c
      :--> (PBuiltinList PTxOut
            :--> (PTxOutRef :--> PBuiltinList PTxOut)))
plam ((Term s (PBuiltinList PTxInInfo)
  -> Term s (PBuiltinList PTxOut)
  -> Term s PTxOutRef
  -> Term s (PBuiltinList PTxOut))
 -> Term
      s
      (PBuiltinList PTxInInfo
       :--> (PBuiltinList PTxOut
             :--> (PTxOutRef :--> PBuiltinList PTxOut))))
-> (Term s (PBuiltinList PTxInInfo)
    -> Term s (PBuiltinList PTxOut)
    -> Term s PTxOutRef
    -> Term s (PBuiltinList PTxOut))
-> Term
     s
     (PBuiltinList PTxInInfo
      :--> (PBuiltinList PTxOut
            :--> (PTxOutRef :--> PBuiltinList PTxOut)))
forall a b. (a -> b) -> a -> b
$ \Term s (PBuiltinList PTxInInfo)
inputs Term s (PBuiltinList PTxOut)
outputs Term s PTxOutRef
outRef ->
    Term s (PMaybe PTxInInfo)
-> (PMaybe PTxInInfo s -> Term s (PBuiltinList PTxOut))
-> Term s (PBuiltinList PTxOut)
forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch (Term
  s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo))
forall (s :: S).
Term
  s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo))
pfindOwnInput Term
  s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo))
-> Term s (PBuiltinList PTxInInfo)
-> Term s (PTxOutRef :--> PMaybe PTxInInfo)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PBuiltinList PTxInInfo)
inputs Term s (PTxOutRef :--> PMaybe PTxInInfo)
-> Term s PTxOutRef -> Term s (PMaybe PTxInInfo)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PTxOutRef
outRef) ((PMaybe PTxInInfo s -> Term s (PBuiltinList PTxOut))
 -> Term s (PBuiltinList PTxOut))
-> (PMaybe PTxInInfo s -> Term s (PBuiltinList PTxOut))
-> Term s (PBuiltinList PTxOut)
forall a b. (a -> b) -> a -> b
$ \case
      PJust Term s PTxInInfo
tx -> do
        let resolved :: Term s (PAsData PTxOut)
resolved = forall (name :: Symbol) (b :: PType) (p :: PType) (s :: S)
       (a :: PType) (as :: [PLabeledType]) (n :: Nat).
(PDataFields p, as ~ PFields p, n ~ PLabelIndex name as,
 KnownNat n, a ~ PUnLabel (IndexList n as), PFromDataable a b) =>
Term s (p :--> b)
pfield @"resolved" Term s (PTxInInfo :--> PAsData PTxOut)
-> Term s PTxInInfo -> Term s (PAsData PTxOut)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PTxInInfo
tx
            outAddr :: Term s PAddress
outAddr = forall (name :: Symbol) (b :: PType) (p :: PType) (s :: S)
       (a :: PType) (as :: [PLabeledType]) (n :: Nat).
(PDataFields p, as ~ PFields p, n ~ PLabelIndex name as,
 KnownNat n, a ~ PUnLabel (IndexList n as), PFromDataable a b) =>
Term s (p :--> b)
pfield @"address" Term s (PAsData PTxOut :--> PAddress)
-> Term s (PAsData PTxOut) -> Term s PAddress
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PAsData PTxOut)
resolved
        Term
  s
  ((PTxOut :--> PBool)
   :--> (PBuiltinList PTxOut :--> PBuiltinList PTxOut))
forall (list :: PType -> PType) (a :: PType) (s :: S).
PIsListLike list a =>
Term s ((a :--> PBool) :--> (list a :--> list a))
pfilter Term
  s
  ((PTxOut :--> PBool)
   :--> (PBuiltinList PTxOut :--> PBuiltinList PTxOut))
-> Term s (PTxOut :--> PBool)
-> Term s (PBuiltinList PTxOut :--> PBuiltinList PTxOut)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s (PAddress :--> (PTxOut :--> PBool))
forall (s' :: S). Term s' (PAddress :--> (PTxOut :--> PBool))
matches Term s (PAddress :--> (PTxOut :--> PBool))
-> Term s PAddress -> Term s (PTxOut :--> PBool)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PAddress
outAddr) Term s (PBuiltinList PTxOut :--> PBuiltinList PTxOut)
-> Term s (PBuiltinList PTxOut) -> Term s (PBuiltinList PTxOut)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PBuiltinList PTxOut)
outputs
      PMaybe PTxInInfo s
PNothing ->
        Term s PString -> Term s (PBuiltinList PTxOut)
forall (a :: PType) (s :: S). Term s PString -> Term s a
ptraceInfoError Term s PString
"can't get any continuing outputs"
  where
    matches ::
      forall (s' :: S).
      Term s' (Address.PAddress :--> V2Tx.PTxOut :--> PBool)
    matches :: forall (s' :: S). Term s' (PAddress :--> (PTxOut :--> PBool))
matches = (forall (s' :: S). Term s' (PAddress :--> (PTxOut :--> PBool)))
-> Term s' (PAddress :--> (PTxOut :--> PBool))
forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic ((forall (s' :: S). Term s' (PAddress :--> (PTxOut :--> PBool)))
 -> Term s' (PAddress :--> (PTxOut :--> PBool)))
-> (forall (s' :: S). Term s' (PAddress :--> (PTxOut :--> PBool)))
-> Term s' (PAddress :--> (PTxOut :--> PBool))
forall a b. (a -> b) -> a -> b
$
      (Term s PAddress -> Term s PTxOut -> Term s PBool)
-> Term s (PAddress :--> (PTxOut :--> PBool))
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: PType).
HasCallStack =>
(Term s c -> Term s PTxOut -> Term s PBool)
-> Term s (c :--> (PTxOut :--> PBool))
plam ((Term s PAddress -> Term s PTxOut -> Term s PBool)
 -> Term s (PAddress :--> (PTxOut :--> PBool)))
-> (Term s PAddress -> Term s PTxOut -> Term s PBool)
-> Term s (PAddress :--> (PTxOut :--> PBool))
forall a b. (a -> b) -> a -> b
$ \Term s PAddress
adr Term s PTxOut
txOut ->
        Term s PAddress
adr Term s PAddress -> Term s PAddress -> Term s PBool
forall (s :: S). Term s PAddress -> Term s PAddress -> Term s PBool
forall (t :: PType) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== forall (name :: Symbol) (b :: PType) (p :: PType) (s :: S)
       (a :: PType) (as :: [PLabeledType]) (n :: Nat).
(PDataFields p, as ~ PFields p, n ~ PLabelIndex name as,
 KnownNat n, a ~ PUnLabel (IndexList n as), PFromDataable a b) =>
Term s (p :--> b)
pfield @"address" Term s (PTxOut :--> PAddress) -> Term s PTxOut -> Term s PAddress
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PTxOut
txOut

{- | Find the input being spent in the current transaction.

  Takes as arguments the inputs, as well as the spending transaction referenced from `PScriptPurpose`.

  __Example:__

  @
  ctx <- tcont $ pletFields @["txInfo", "purpose"] sc
  pmatchC (getField @"purpose" ctx) >>= \case
    PSpending outRef' -> do
      let outRef = pfield @"_0" # outRef'
          inputs = pfield @"inputs" # (getField @"txInfo" ctx)
      pure $ pfindOwnInput # inputs # outRef
    _ ->
      pure $ ptraceInfoError "not a spending tx"
  @

  @since 2.1.0
-}
pfindOwnInput ::
  forall (s :: S).
  Term
    s
    ( PBuiltinList Contexts.PTxInInfo
        :--> V3Tx.PTxOutRef
        :--> PMaybe Contexts.PTxInInfo
    )
pfindOwnInput :: forall (s :: S).
Term
  s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo))
pfindOwnInput = (forall (s :: S).
 Term
   s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo)))
-> Term
     s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo))
forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic ((forall (s :: S).
  Term
    s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo)))
 -> Term
      s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo)))
-> (forall (s :: S).
    Term
      s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo)))
-> Term
     s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo))
forall a b. (a -> b) -> a -> b
$
  (Term s (PBuiltinList PTxInInfo)
 -> Term s PTxOutRef -> Term s (PMaybe PTxInInfo))
-> Term
     s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo))
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: PType).
HasCallStack =>
(Term s c -> Term s PTxOutRef -> Term s (PMaybe PTxInInfo))
-> Term s (c :--> (PTxOutRef :--> PMaybe PTxInInfo))
plam ((Term s (PBuiltinList PTxInInfo)
  -> Term s PTxOutRef -> Term s (PMaybe PTxInInfo))
 -> Term
      s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo)))
-> (Term s (PBuiltinList PTxInInfo)
    -> Term s PTxOutRef -> Term s (PMaybe PTxInInfo))
-> Term
     s (PBuiltinList PTxInInfo :--> (PTxOutRef :--> PMaybe PTxInInfo))
forall a b. (a -> b) -> a -> b
$ \Term s (PBuiltinList PTxInInfo)
inputs Term s PTxOutRef
outRef ->
    Term
  s
  ((PTxInInfo :--> PBool)
   :--> (PBuiltinList PTxInInfo :--> PMaybe PTxInInfo))
forall (l :: PType -> PType) (a :: PType) (s :: S).
PIsListLike l a =>
Term s ((a :--> PBool) :--> (l a :--> PMaybe a))
pfind Term
  s
  ((PTxInInfo :--> PBool)
   :--> (PBuiltinList PTxInInfo :--> PMaybe PTxInInfo))
-> Term s (PTxInInfo :--> PBool)
-> Term s (PBuiltinList PTxInInfo :--> PMaybe PTxInInfo)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# (Term s (PTxOutRef :--> (PTxInInfo :--> PBool))
forall (s' :: S). Term s' (PTxOutRef :--> (PTxInInfo :--> PBool))
matches Term s (PTxOutRef :--> (PTxInInfo :--> PBool))
-> Term s PTxOutRef -> Term s (PTxInInfo :--> PBool)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PTxOutRef
outRef) Term s (PBuiltinList PTxInInfo :--> PMaybe PTxInInfo)
-> Term s (PBuiltinList PTxInInfo) -> Term s (PMaybe PTxInInfo)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PBuiltinList PTxInInfo)
inputs
  where
    matches ::
      forall (s' :: S).
      Term s' (V3Tx.PTxOutRef :--> Contexts.PTxInInfo :--> PBool)
    matches :: forall (s' :: S). Term s' (PTxOutRef :--> (PTxInInfo :--> PBool))
matches = (forall (s' :: S). Term s' (PTxOutRef :--> (PTxInInfo :--> PBool)))
-> Term s' (PTxOutRef :--> (PTxInInfo :--> PBool))
forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic ((forall (s' :: S).
  Term s' (PTxOutRef :--> (PTxInInfo :--> PBool)))
 -> Term s' (PTxOutRef :--> (PTxInInfo :--> PBool)))
-> (forall (s' :: S).
    Term s' (PTxOutRef :--> (PTxInInfo :--> PBool)))
-> Term s' (PTxOutRef :--> (PTxInInfo :--> PBool))
forall a b. (a -> b) -> a -> b
$
      (Term s PTxOutRef -> Term s PTxInInfo -> Term s PBool)
-> Term s (PTxOutRef :--> (PTxInInfo :--> PBool))
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: PType).
HasCallStack =>
(Term s c -> Term s PTxInInfo -> Term s PBool)
-> Term s (c :--> (PTxInInfo :--> PBool))
plam ((Term s PTxOutRef -> Term s PTxInInfo -> Term s PBool)
 -> Term s (PTxOutRef :--> (PTxInInfo :--> PBool)))
-> (Term s PTxOutRef -> Term s PTxInInfo -> Term s PBool)
-> Term s (PTxOutRef :--> (PTxInInfo :--> PBool))
forall a b. (a -> b) -> a -> b
$ \Term s PTxOutRef
outref Term s PTxInInfo
txininfo ->
        Term s PTxOutRef
outref Term s PTxOutRef -> Term s PTxOutRef -> Term s PBool
forall (s :: S).
Term s PTxOutRef -> Term s PTxOutRef -> Term s PBool
forall (t :: PType) (s :: S).
PEq t =>
Term s t -> Term s t -> Term s PBool
#== forall (name :: Symbol) (b :: PType) (p :: PType) (s :: S)
       (a :: PType) (as :: [PLabeledType]) (n :: Nat).
(PDataFields p, as ~ PFields p, n ~ PLabelIndex name as,
 KnownNat n, a ~ PUnLabel (IndexList n as), PFromDataable a b) =>
Term s (p :--> b)
pfield @"outRef" Term s (PTxInInfo :--> PTxOutRef)
-> Term s PTxInInfo -> Term s PTxOutRef
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PTxInInfo
txininfo

{- | Lookup up the datum given the datum hash.

  Takes as argument the datum assoc list from a `PTxInfo`. Validates the datum
  using `PTryFrom`.

  __Example:__

  @
  pparseDatum @MyType # datumHash #$ pfield @"datums" # txinfo
  @

  @since 2.1.2
-}
pparseDatum ::
  forall (a :: S -> Type) (s :: S).
  PTryFrom PData (PAsData a) =>
  Term s (Scripts.PDatumHash :--> AssocMap.PMap 'AssocMap.Unsorted Scripts.PDatumHash Scripts.PDatum :--> PMaybe (PAsData a))
pparseDatum :: forall (a :: PType) (s :: S).
PTryFrom PData (PAsData a) =>
Term
  s
  (PDatumHash
   :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe (PAsData a)))
pparseDatum = ClosedTerm
  (PDatumHash
   :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe (PAsData a)))
-> Term
     s
     (PDatumHash
      :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe (PAsData a)))
forall (a :: PType) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic (ClosedTerm
   (PDatumHash
    :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe (PAsData a)))
 -> Term
      s
      (PDatumHash
       :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe (PAsData a))))
-> ClosedTerm
     (PDatumHash
      :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe (PAsData a)))
-> Term
     s
     (PDatumHash
      :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe (PAsData a)))
forall a b. (a -> b) -> a -> b
$ (Term s PDatumHash
 -> Term s (PMap 'Unsorted PDatumHash PDatum)
 -> Term s (PMaybe (PAsData a)))
-> Term
     s
     (PDatumHash
      :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe (PAsData a)))
forall a (b :: PType) (s :: S) (c :: PType).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: PType).
HasCallStack =>
(Term s c
 -> Term s (PMap 'Unsorted PDatumHash PDatum)
 -> Term s (PMaybe (PAsData a)))
-> Term
     s
     (c :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe (PAsData a)))
plam ((Term s PDatumHash
  -> Term s (PMap 'Unsorted PDatumHash PDatum)
  -> Term s (PMaybe (PAsData a)))
 -> Term
      s
      (PDatumHash
       :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe (PAsData a))))
-> (Term s PDatumHash
    -> Term s (PMap 'Unsorted PDatumHash PDatum)
    -> Term s (PMaybe (PAsData a)))
-> Term
     s
     (PDatumHash
      :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe (PAsData a)))
forall a b. (a -> b) -> a -> b
$ \Term s PDatumHash
dh Term s (PMap 'Unsorted PDatumHash PDatum)
datums ->
  Term s (PMaybe PDatum)
-> (PMaybe PDatum s -> Term s (PMaybe (PAsData a)))
-> Term s (PMaybe (PAsData a))
forall (a :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch (Term
  s
  (PDatumHash
   :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe PDatum))
forall (k :: PType) (v :: PType) (any :: KeyGuarantees) (s :: S).
(PIsData k, PIsData v) =>
Term s (k :--> (PMap any k v :--> PMaybe v))
AssocMap.plookup Term
  s
  (PDatumHash
   :--> (PMap 'Unsorted PDatumHash PDatum :--> PMaybe PDatum))
-> Term s PDatumHash
-> Term s (PMap 'Unsorted PDatumHash PDatum :--> PMaybe PDatum)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PDatumHash
dh Term s (PMap 'Unsorted PDatumHash PDatum :--> PMaybe PDatum)
-> Term s (PMap 'Unsorted PDatumHash PDatum)
-> Term s (PMaybe PDatum)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PMap 'Unsorted PDatumHash PDatum)
datums) ((PMaybe PDatum s -> Term s (PMaybe (PAsData a)))
 -> Term s (PMaybe (PAsData a)))
-> (PMaybe PDatum s -> Term s (PMaybe (PAsData a)))
-> Term s (PMaybe (PAsData a))
forall a b. (a -> b) -> a -> b
$ \case
    PMaybe PDatum s
PNothing -> PMaybe (PAsData a) s -> Term s (PMaybe (PAsData a))
forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon PMaybe (PAsData a) s
forall (a :: PType) (s :: S). PMaybe a s
PNothing
    PJust Term s PDatum
datum -> PMaybe (PAsData a) s -> Term s (PMaybe (PAsData a))
forall (a :: PType) (s :: S). PlutusType a => a s -> Term s a
pcon (PMaybe (PAsData a) s -> Term s (PMaybe (PAsData a)))
-> (Term s (PAsData a) -> PMaybe (PAsData a) s)
-> Term s (PAsData a)
-> Term s (PMaybe (PAsData a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Term s (PAsData a) -> PMaybe (PAsData a) s
forall (a :: PType) (s :: S). Term s a -> PMaybe a s
PJust (Term s (PAsData a) -> Term s (PMaybe (PAsData a)))
-> Term s (PAsData a) -> Term s (PMaybe (PAsData a))
forall a b. (a -> b) -> a -> b
$ Term s (PInner PDatum)
-> ((Term s (PAsData a),
     Reduce (PTryFromExcess (PInner PDatum) (PAsData a) s))
    -> Term s (PAsData a))
-> Term s (PAsData a)
forall (b :: PType) (a :: PType) (s :: S) (r :: PType).
PTryFrom a b =>
Term s a
-> ((Term s b, Reduce (PTryFromExcess a b s)) -> Term s r)
-> Term s r
ptryFrom (Term s PDatum -> Term s (PInner PDatum)
forall (s :: S) (a :: PType). Term s a -> Term s (PInner a)
pto Term s PDatum
datum) (Term s (PAsData a),
 Reduce (PTryFromExcess (PInner PDatum) (PAsData a) s))
-> Term s (PAsData a)
(Term s (PAsData a),
 GReduce
   (PTryFromExcess (PInner PDatum) (PAsData a) s)
   (Rep (PTryFromExcess (PInner PDatum) (PAsData a) s)))
-> Term s (PAsData a)
forall a b. (a, b) -> a
fst

-- Helpers

hashScriptWithPrefix :: ByteString -> Script -> Plutus.ScriptHash
hashScriptWithPrefix :: ByteString -> Script -> ScriptHash
hashScriptWithPrefix ByteString
prefix Script
scr =
  BuiltinByteString -> ScriptHash
Plutus.ScriptHash (BuiltinByteString -> ScriptHash)
-> (ByteString -> BuiltinByteString) -> ByteString -> ScriptHash
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> BuiltinByteString
hashBlake2b_224 (ByteString -> ScriptHash) -> ByteString -> ScriptHash
forall a b. (a -> b) -> a -> b
$
    ByteString
prefix ByteString -> ByteString -> ByteString
forall a. Semigroup a => a -> a -> a
<> (ShortByteString -> ByteString
fromShort (ShortByteString -> ByteString)
-> (Script -> ShortByteString) -> Script -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Program DeBruijn DefaultUni DefaultFun () -> ShortByteString
serialiseUPLC (Program DeBruijn DefaultUni DefaultFun () -> ShortByteString)
-> (Script -> Program DeBruijn DefaultUni DefaultFun ())
-> Script
-> ShortByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Script -> Program DeBruijn DefaultUni DefaultFun ()
unScript (Script -> ByteString) -> Script -> ByteString
forall a b. (a -> b) -> a -> b
$ Script
scr)

hashLedgerBytes :: Plutus.LedgerBytes -> PlutusTx.BuiltinByteString
hashLedgerBytes :: LedgerBytes -> BuiltinByteString
hashLedgerBytes = ByteString -> BuiltinByteString
hashBlake2b_224 (ByteString -> BuiltinByteString)
-> (LedgerBytes -> ByteString) -> LedgerBytes -> BuiltinByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BuiltinByteString -> ByteString
BuiltinByteString -> FromBuiltin BuiltinByteString
forall arep. HasFromBuiltin arep => arep -> FromBuiltin arep
PlutusTx.fromBuiltin (BuiltinByteString -> ByteString)
-> (LedgerBytes -> BuiltinByteString) -> LedgerBytes -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LedgerBytes -> BuiltinByteString
Plutus.getLedgerBytes

hashBlake2b_224 :: ByteString -> PlutusTx.BuiltinByteString
hashBlake2b_224 :: ByteString -> BuiltinByteString
hashBlake2b_224 = ByteString -> BuiltinByteString
ByteString -> ToBuiltin ByteString
forall a. HasToBuiltin a => a -> ToBuiltin a
PlutusTx.toBuiltin (ByteString -> BuiltinByteString)
-> (ByteString -> ByteString) -> ByteString -> BuiltinByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert @_ @ByteString (Digest Blake2b_224 -> ByteString)
-> (ByteString -> Digest Blake2b_224) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blake2b_224 -> ByteString -> Digest Blake2b_224
forall ba alg.
(ByteArrayAccess ba, HashAlgorithm alg) =>
alg -> ba -> Digest alg
hashWith Blake2b_224
Blake2b_224

hashBlake2b_256 :: ByteString -> PlutusTx.BuiltinByteString
hashBlake2b_256 :: ByteString -> BuiltinByteString
hashBlake2b_256 = ByteString -> BuiltinByteString
ByteString -> ToBuiltin ByteString
forall a. HasToBuiltin a => a -> ToBuiltin a
PlutusTx.toBuiltin (ByteString -> BuiltinByteString)
-> (ByteString -> ByteString) -> ByteString -> BuiltinByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall bin bout.
(ByteArrayAccess bin, ByteArray bout) =>
bin -> bout
convert @_ @ByteString (Digest Blake2b_256 -> ByteString)
-> (ByteString -> Digest Blake2b_256) -> ByteString -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Blake2b_256 -> ByteString -> Digest Blake2b_256
forall ba alg.
(ByteArrayAccess ba, HashAlgorithm alg) =>
alg -> ba -> Digest alg
hashWith Blake2b_256
Blake2b_256

hashData :: Plutus.Data -> PlutusTx.BuiltinByteString
hashData :: Data -> BuiltinByteString
hashData = ByteString -> BuiltinByteString
hashBlake2b_256 (ByteString -> BuiltinByteString)
-> (Data -> ByteString) -> Data -> BuiltinByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ByteString -> ByteString
toStrict (ByteString -> ByteString)
-> (Data -> ByteString) -> Data -> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Data -> ByteString
forall a. Serialise a => a -> ByteString
serialise