module Cardano.YTxP.Control.Yielding (
getAuthorisedScriptHash,
PAuthorisedScriptPurpose (PMinting, PSpending, PRewarding),
PYieldingRedeemer (..),
)
where
import Cardano.YTxP.SDK.Redeemers (
AuthorisedScriptIndex (AuthorisedScriptIndex),
AuthorisedScriptProofIndex (AuthorisedScriptProofIndex),
AuthorisedScriptPurpose (Minting, Rewarding, Spending),
YieldingRedeemer,
)
import Data.Coerce (coerce)
import GHC.Generics (Generic)
import Generics.SOP qualified as SOP
import Plutarch.Internal.Lift (LiftError (OtherLiftError))
import Plutarch.LedgerApi.Utils (PMaybeData (PDJust, PDNothing))
import Plutarch.LedgerApi.V3 (
PCurrencySymbol,
PScriptHash,
PTxInInfo,
PTxOut (ptxOut'value),
ptxInInfo'resolved,
ptxOut'referenceScript,
)
import Plutarch.Repr.Tag (DeriveAsTag (DeriveAsTag))
import Utils (pmember)
newtype PAuthorisedScriptIndex (s :: S) = PAuthorisedScriptIndex (Term s PInteger)
deriving stock ((forall x.
PAuthorisedScriptIndex s -> Rep (PAuthorisedScriptIndex s) x)
-> (forall x.
Rep (PAuthorisedScriptIndex s) x -> PAuthorisedScriptIndex s)
-> Generic (PAuthorisedScriptIndex s)
forall x.
Rep (PAuthorisedScriptIndex s) x -> PAuthorisedScriptIndex s
forall x.
PAuthorisedScriptIndex s -> Rep (PAuthorisedScriptIndex s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x.
Rep (PAuthorisedScriptIndex s) x -> PAuthorisedScriptIndex s
forall (s :: S) x.
PAuthorisedScriptIndex s -> Rep (PAuthorisedScriptIndex s) x
$cfrom :: forall (s :: S) x.
PAuthorisedScriptIndex s -> Rep (PAuthorisedScriptIndex s) x
from :: forall x.
PAuthorisedScriptIndex s -> Rep (PAuthorisedScriptIndex s) x
$cto :: forall (s :: S) x.
Rep (PAuthorisedScriptIndex s) x -> PAuthorisedScriptIndex s
to :: forall x.
Rep (PAuthorisedScriptIndex s) x -> PAuthorisedScriptIndex s
Generic)
deriving anyclass (All @[Type] (SListI @Type) (Code (PAuthorisedScriptIndex s))
All @[Type] (SListI @Type) (Code (PAuthorisedScriptIndex s)) =>
(PAuthorisedScriptIndex s -> Rep (PAuthorisedScriptIndex s))
-> (Rep (PAuthorisedScriptIndex s) -> PAuthorisedScriptIndex s)
-> Generic (PAuthorisedScriptIndex s)
Rep (PAuthorisedScriptIndex s) -> PAuthorisedScriptIndex s
PAuthorisedScriptIndex s -> Rep (PAuthorisedScriptIndex s)
forall a.
All @[Type] (SListI @Type) (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (s :: S).
All @[Type] (SListI @Type) (Code (PAuthorisedScriptIndex s))
forall (s :: S).
Rep (PAuthorisedScriptIndex s) -> PAuthorisedScriptIndex s
forall (s :: S).
PAuthorisedScriptIndex s -> Rep (PAuthorisedScriptIndex s)
$cfrom :: forall (s :: S).
PAuthorisedScriptIndex s -> Rep (PAuthorisedScriptIndex s)
from :: PAuthorisedScriptIndex s -> Rep (PAuthorisedScriptIndex s)
$cto :: forall (s :: S).
Rep (PAuthorisedScriptIndex s) -> PAuthorisedScriptIndex s
to :: Rep (PAuthorisedScriptIndex s) -> PAuthorisedScriptIndex s
SOP.Generic, (forall (s :: S).
Term s (PAsData PAuthorisedScriptIndex)
-> Term s PAuthorisedScriptIndex)
-> (forall (s :: S). Term s PAuthorisedScriptIndex -> Term s PData)
-> PIsData PAuthorisedScriptIndex
forall (s :: S).
Term s (PAsData PAuthorisedScriptIndex)
-> Term s PAuthorisedScriptIndex
forall (s :: S). Term s PAuthorisedScriptIndex -> Term s PData
forall (a :: S -> Type).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
$cpfromDataImpl :: forall (s :: S).
Term s (PAsData PAuthorisedScriptIndex)
-> Term s PAuthorisedScriptIndex
pfromDataImpl :: forall (s :: S).
Term s (PAsData PAuthorisedScriptIndex)
-> Term s PAuthorisedScriptIndex
$cpdataImpl :: forall (s :: S). Term s PAuthorisedScriptIndex -> Term s PData
pdataImpl :: forall (s :: S). Term s PAuthorisedScriptIndex -> Term s PData
PIsData)
deriving ((forall (s :: S).
PAuthorisedScriptIndex s -> Term s (PInner PAuthorisedScriptIndex))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner PAuthorisedScriptIndex)
-> (PAuthorisedScriptIndex s -> Term s b) -> Term s b)
-> PlutusType PAuthorisedScriptIndex
forall (s :: S).
PAuthorisedScriptIndex s -> Term s (PInner PAuthorisedScriptIndex)
forall (s :: S) (b :: S -> Type).
Term s (PInner PAuthorisedScriptIndex)
-> (PAuthorisedScriptIndex s -> Term s b) -> Term s b
forall (a :: S -> Type).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
$cpcon' :: forall (s :: S).
PAuthorisedScriptIndex s -> Term s (PInner PAuthorisedScriptIndex)
pcon' :: forall (s :: S).
PAuthorisedScriptIndex s -> Term s (PInner PAuthorisedScriptIndex)
$cpmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PAuthorisedScriptIndex)
-> (PAuthorisedScriptIndex s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PAuthorisedScriptIndex)
-> (PAuthorisedScriptIndex s -> Term s b) -> Term s b
PlutusType) via (DeriveNewtypePlutusType PAuthorisedScriptIndex)
deriving
(PlutusType PAuthorisedScriptIndex
AsHaskell PAuthorisedScriptIndex
-> PlutusRepr PAuthorisedScriptIndex
PlutusRepr PAuthorisedScriptIndex
-> Either LiftError (AsHaskell PAuthorisedScriptIndex)
PlutusType PAuthorisedScriptIndex =>
(AsHaskell PAuthorisedScriptIndex
-> PlutusRepr PAuthorisedScriptIndex)
-> (PlutusRepr PAuthorisedScriptIndex
-> Either LiftError (AsHaskell PAuthorisedScriptIndex))
-> (forall (s :: S).
PlutusRepr PAuthorisedScriptIndex
-> PLifted s PAuthorisedScriptIndex)
-> ((forall (s :: S). PLifted s PAuthorisedScriptIndex)
-> Either LiftError (PlutusRepr PAuthorisedScriptIndex))
-> PLiftable PAuthorisedScriptIndex
(forall (s :: S). PLifted s PAuthorisedScriptIndex)
-> Either LiftError (PlutusRepr PAuthorisedScriptIndex)
forall (s :: S).
PlutusRepr PAuthorisedScriptIndex
-> PLifted s PAuthorisedScriptIndex
forall (a :: S -> Type).
PlutusType a =>
(AsHaskell a -> PlutusRepr a)
-> (PlutusRepr a -> Either LiftError (AsHaskell a))
-> (forall (s :: S). PlutusRepr a -> PLifted s a)
-> ((forall (s :: S). PLifted s a)
-> Either LiftError (PlutusRepr a))
-> PLiftable a
$chaskToRepr :: AsHaskell PAuthorisedScriptIndex
-> PlutusRepr PAuthorisedScriptIndex
haskToRepr :: AsHaskell PAuthorisedScriptIndex
-> PlutusRepr PAuthorisedScriptIndex
$creprToHask :: PlutusRepr PAuthorisedScriptIndex
-> Either LiftError (AsHaskell PAuthorisedScriptIndex)
reprToHask :: PlutusRepr PAuthorisedScriptIndex
-> Either LiftError (AsHaskell PAuthorisedScriptIndex)
$creprToPlut :: forall (s :: S).
PlutusRepr PAuthorisedScriptIndex
-> PLifted s PAuthorisedScriptIndex
reprToPlut :: forall (s :: S).
PlutusRepr PAuthorisedScriptIndex
-> PLifted s PAuthorisedScriptIndex
$cplutToRepr :: (forall (s :: S). PLifted s PAuthorisedScriptIndex)
-> Either LiftError (PlutusRepr PAuthorisedScriptIndex)
plutToRepr :: (forall (s :: S). PLifted s PAuthorisedScriptIndex)
-> Either LiftError (PlutusRepr PAuthorisedScriptIndex)
PLiftable)
via (DeriveNewtypePLiftable PAuthorisedScriptIndex AuthorisedScriptIndex)
instance PTryFrom PData (PAsData PAuthorisedScriptIndex)
data PAuthorisedScriptPurpose (s :: S) = PMinting | PSpending | PRewarding
deriving stock ((forall x.
PAuthorisedScriptPurpose s -> Rep (PAuthorisedScriptPurpose s) x)
-> (forall x.
Rep (PAuthorisedScriptPurpose s) x -> PAuthorisedScriptPurpose s)
-> Generic (PAuthorisedScriptPurpose s)
forall x.
Rep (PAuthorisedScriptPurpose s) x -> PAuthorisedScriptPurpose s
forall x.
PAuthorisedScriptPurpose s -> Rep (PAuthorisedScriptPurpose s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x.
Rep (PAuthorisedScriptPurpose s) x -> PAuthorisedScriptPurpose s
forall (s :: S) x.
PAuthorisedScriptPurpose s -> Rep (PAuthorisedScriptPurpose s) x
$cfrom :: forall (s :: S) x.
PAuthorisedScriptPurpose s -> Rep (PAuthorisedScriptPurpose s) x
from :: forall x.
PAuthorisedScriptPurpose s -> Rep (PAuthorisedScriptPurpose s) x
$cto :: forall (s :: S) x.
Rep (PAuthorisedScriptPurpose s) x -> PAuthorisedScriptPurpose s
to :: forall x.
Rep (PAuthorisedScriptPurpose s) x -> PAuthorisedScriptPurpose s
Generic, Int -> PAuthorisedScriptPurpose s
PAuthorisedScriptPurpose s -> Int
PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s]
PAuthorisedScriptPurpose s -> PAuthorisedScriptPurpose s
PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s]
PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s
-> [PAuthorisedScriptPurpose s]
(PAuthorisedScriptPurpose s -> PAuthorisedScriptPurpose s)
-> (PAuthorisedScriptPurpose s -> PAuthorisedScriptPurpose s)
-> (Int -> PAuthorisedScriptPurpose s)
-> (PAuthorisedScriptPurpose s -> Int)
-> (PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s])
-> (PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s])
-> (PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s])
-> (PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s
-> [PAuthorisedScriptPurpose s])
-> Enum (PAuthorisedScriptPurpose s)
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
forall (s :: S). Int -> PAuthorisedScriptPurpose s
forall (s :: S). PAuthorisedScriptPurpose s -> Int
forall (s :: S).
PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s]
forall (s :: S).
PAuthorisedScriptPurpose s -> PAuthorisedScriptPurpose s
forall (s :: S).
PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s]
forall (s :: S).
PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s
-> [PAuthorisedScriptPurpose s]
$csucc :: forall (s :: S).
PAuthorisedScriptPurpose s -> PAuthorisedScriptPurpose s
succ :: PAuthorisedScriptPurpose s -> PAuthorisedScriptPurpose s
$cpred :: forall (s :: S).
PAuthorisedScriptPurpose s -> PAuthorisedScriptPurpose s
pred :: PAuthorisedScriptPurpose s -> PAuthorisedScriptPurpose s
$ctoEnum :: forall (s :: S). Int -> PAuthorisedScriptPurpose s
toEnum :: Int -> PAuthorisedScriptPurpose s
$cfromEnum :: forall (s :: S). PAuthorisedScriptPurpose s -> Int
fromEnum :: PAuthorisedScriptPurpose s -> Int
$cenumFrom :: forall (s :: S).
PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s]
enumFrom :: PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s]
$cenumFromThen :: forall (s :: S).
PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s]
enumFromThen :: PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s]
$cenumFromTo :: forall (s :: S).
PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s]
enumFromTo :: PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s -> [PAuthorisedScriptPurpose s]
$cenumFromThenTo :: forall (s :: S).
PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s
-> [PAuthorisedScriptPurpose s]
enumFromThenTo :: PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s
-> [PAuthorisedScriptPurpose s]
Enum, PAuthorisedScriptPurpose s
PAuthorisedScriptPurpose s
-> PAuthorisedScriptPurpose s
-> Bounded (PAuthorisedScriptPurpose s)
forall a. a -> a -> Bounded a
forall (s :: S). PAuthorisedScriptPurpose s
$cminBound :: forall (s :: S). PAuthorisedScriptPurpose s
minBound :: PAuthorisedScriptPurpose s
$cmaxBound :: forall (s :: S). PAuthorisedScriptPurpose s
maxBound :: PAuthorisedScriptPurpose s
Bounded)
deriving anyclass (All @[Type] (SListI @Type) (Code (PAuthorisedScriptPurpose s))
All @[Type] (SListI @Type) (Code (PAuthorisedScriptPurpose s)) =>
(PAuthorisedScriptPurpose s -> Rep (PAuthorisedScriptPurpose s))
-> (Rep (PAuthorisedScriptPurpose s) -> PAuthorisedScriptPurpose s)
-> Generic (PAuthorisedScriptPurpose s)
Rep (PAuthorisedScriptPurpose s) -> PAuthorisedScriptPurpose s
PAuthorisedScriptPurpose s -> Rep (PAuthorisedScriptPurpose s)
forall a.
All @[Type] (SListI @Type) (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (s :: S).
All @[Type] (SListI @Type) (Code (PAuthorisedScriptPurpose s))
forall (s :: S).
Rep (PAuthorisedScriptPurpose s) -> PAuthorisedScriptPurpose s
forall (s :: S).
PAuthorisedScriptPurpose s -> Rep (PAuthorisedScriptPurpose s)
$cfrom :: forall (s :: S).
PAuthorisedScriptPurpose s -> Rep (PAuthorisedScriptPurpose s)
from :: PAuthorisedScriptPurpose s -> Rep (PAuthorisedScriptPurpose s)
$cto :: forall (s :: S).
Rep (PAuthorisedScriptPurpose s) -> PAuthorisedScriptPurpose s
to :: Rep (PAuthorisedScriptPurpose s) -> PAuthorisedScriptPurpose s
SOP.Generic, (forall (s :: S).
Term s (PAsData PAuthorisedScriptPurpose)
-> Term s PAuthorisedScriptPurpose)
-> (forall (s :: S).
Term s PAuthorisedScriptPurpose -> Term s PData)
-> PIsData PAuthorisedScriptPurpose
forall (s :: S).
Term s (PAsData PAuthorisedScriptPurpose)
-> Term s PAuthorisedScriptPurpose
forall (s :: S). Term s PAuthorisedScriptPurpose -> Term s PData
forall (a :: S -> Type).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
$cpfromDataImpl :: forall (s :: S).
Term s (PAsData PAuthorisedScriptPurpose)
-> Term s PAuthorisedScriptPurpose
pfromDataImpl :: forall (s :: S).
Term s (PAsData PAuthorisedScriptPurpose)
-> Term s PAuthorisedScriptPurpose
$cpdataImpl :: forall (s :: S). Term s PAuthorisedScriptPurpose -> Term s PData
pdataImpl :: forall (s :: S). Term s PAuthorisedScriptPurpose -> Term s PData
PIsData, (forall (s :: S).
Term s PAuthorisedScriptPurpose
-> Term s PAuthorisedScriptPurpose -> Term s PBool)
-> PEq PAuthorisedScriptPurpose
forall (s :: S).
Term s PAuthorisedScriptPurpose
-> Term s PAuthorisedScriptPurpose -> Term s PBool
forall (t :: S -> Type).
(forall (s :: S). Term s t -> Term s t -> Term s PBool) -> PEq t
$c#== :: forall (s :: S).
Term s PAuthorisedScriptPurpose
-> Term s PAuthorisedScriptPurpose -> Term s PBool
#== :: forall (s :: S).
Term s PAuthorisedScriptPurpose
-> Term s PAuthorisedScriptPurpose -> Term s PBool
PEq)
deriving
((forall (s :: S).
PAuthorisedScriptPurpose s
-> Term s (PInner PAuthorisedScriptPurpose))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner PAuthorisedScriptPurpose)
-> (PAuthorisedScriptPurpose s -> Term s b) -> Term s b)
-> PlutusType PAuthorisedScriptPurpose
forall (s :: S).
PAuthorisedScriptPurpose s
-> Term s (PInner PAuthorisedScriptPurpose)
forall (s :: S) (b :: S -> Type).
Term s (PInner PAuthorisedScriptPurpose)
-> (PAuthorisedScriptPurpose s -> Term s b) -> Term s b
forall (a :: S -> Type).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
$cpcon' :: forall (s :: S).
PAuthorisedScriptPurpose s
-> Term s (PInner PAuthorisedScriptPurpose)
pcon' :: forall (s :: S).
PAuthorisedScriptPurpose s
-> Term s (PInner PAuthorisedScriptPurpose)
$cpmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PAuthorisedScriptPurpose)
-> (PAuthorisedScriptPurpose s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PAuthorisedScriptPurpose)
-> (PAuthorisedScriptPurpose s -> Term s b) -> Term s b
PlutusType)
via DeriveAsTag PAuthorisedScriptPurpose
instance PLiftable PAuthorisedScriptPurpose where
type AsHaskell PAuthorisedScriptPurpose = AuthorisedScriptPurpose
type PlutusRepr PAuthorisedScriptPurpose = Integer
haskToRepr :: AsHaskell PAuthorisedScriptPurpose
-> PlutusRepr PAuthorisedScriptPurpose
haskToRepr = Int -> Integer
forall a. Integral a => a -> Integer
toInteger (Int -> Integer)
-> (AuthorisedScriptPurpose -> Int)
-> AuthorisedScriptPurpose
-> Integer
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SOP
@Type
I
((':)
@[Type]
('[] @Type)
((':)
@[Type] ('[] @Type) ((':) @[Type] ('[] @Type) ('[] @[Type]))))
-> Int
forall k l (h :: (k -> Type) -> l -> Type) (f :: k -> Type)
(xs :: l).
HIndex @k @l h =>
h f xs -> Int
forall (f :: Type -> Type) (xs :: [[Type]]). SOP @Type f xs -> Int
SOP.hindex (SOP
@Type
I
((':)
@[Type]
('[] @Type)
((':)
@[Type] ('[] @Type) ((':) @[Type] ('[] @Type) ('[] @[Type]))))
-> Int)
-> (AuthorisedScriptPurpose
-> SOP
@Type
I
((':)
@[Type]
('[] @Type)
((':)
@[Type] ('[] @Type) ((':) @[Type] ('[] @Type) ('[] @[Type])))))
-> AuthorisedScriptPurpose
-> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. AuthorisedScriptPurpose
-> SOP
@Type
I
((':)
@[Type]
('[] @Type)
((':)
@[Type] ('[] @Type) ((':) @[Type] ('[] @Type) ('[] @[Type]))))
AuthorisedScriptPurpose -> Rep AuthorisedScriptPurpose
forall a. Generic a => a -> Rep a
SOP.from
reprToPlut :: forall (s :: S).
PlutusRepr PAuthorisedScriptPurpose
-> PLifted s PAuthorisedScriptPurpose
reprToPlut PlutusRepr PAuthorisedScriptPurpose
idx = Term s POpaque -> PLifted s PAuthorisedScriptPurpose
forall (s :: S) (a :: S -> Type). Term s POpaque -> PLifted s a
PLifted (Term s POpaque -> PLifted s PAuthorisedScriptPurpose)
-> Term s POpaque -> PLifted s PAuthorisedScriptPurpose
forall a b. (a -> b) -> a -> b
$ Term s PInteger -> Term s POpaque
forall (s :: S) (a :: S -> Type). Term s a -> Term s POpaque
popaque (Term s PInteger -> Term s POpaque)
-> Term s PInteger -> Term s POpaque
forall a b. (a -> b) -> a -> b
$ forall (a :: S -> Type) (s :: S).
PLiftable a =>
AsHaskell a -> Term s a
pconstant @PInteger AsHaskell PInteger
PlutusRepr PAuthorisedScriptPurpose
idx
plutToRepr :: (forall (s :: S). PLifted s PAuthorisedScriptPurpose)
-> Either LiftError (PlutusRepr PAuthorisedScriptPurpose)
plutToRepr forall (s :: S). PLifted s PAuthorisedScriptPurpose
p = forall (a :: S -> Type).
PLiftable a =>
(forall (s :: S). PLifted s a) -> Either LiftError (PlutusRepr a)
plutToRepr @PInteger ((forall (s :: S). PLifted s PInteger)
-> Either LiftError (PlutusRepr PInteger))
-> (forall (s :: S). PLifted s PInteger)
-> Either LiftError (PlutusRepr PInteger)
forall a b. (a -> b) -> a -> b
$ PLifted s PAuthorisedScriptPurpose -> PLifted s PInteger
forall a b. Coercible @Type a b => a -> b
coerce PLifted s PAuthorisedScriptPurpose
forall (s :: S). PLifted s PAuthorisedScriptPurpose
p
reprToHask :: PlutusRepr PAuthorisedScriptPurpose
-> Either LiftError (AsHaskell PAuthorisedScriptPurpose)
reprToHask PlutusRepr PAuthorisedScriptPurpose
idx
| Integer
PlutusRepr PAuthorisedScriptPurpose
idx Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== forall (a :: S -> Type). PLiftable a => AsHaskell a -> PlutusRepr a
haskToRepr @PAuthorisedScriptPurpose AsHaskell PAuthorisedScriptPurpose
AuthorisedScriptPurpose
Minting = AuthorisedScriptPurpose -> Either LiftError AuthorisedScriptPurpose
forall a b. b -> Either a b
Right AuthorisedScriptPurpose
Minting
| Integer
PlutusRepr PAuthorisedScriptPurpose
idx Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== forall (a :: S -> Type). PLiftable a => AsHaskell a -> PlutusRepr a
haskToRepr @PAuthorisedScriptPurpose AsHaskell PAuthorisedScriptPurpose
AuthorisedScriptPurpose
Spending = AuthorisedScriptPurpose -> Either LiftError AuthorisedScriptPurpose
forall a b. b -> Either a b
Right AuthorisedScriptPurpose
Spending
| Integer
PlutusRepr PAuthorisedScriptPurpose
idx Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== forall (a :: S -> Type). PLiftable a => AsHaskell a -> PlutusRepr a
haskToRepr @PAuthorisedScriptPurpose AsHaskell PAuthorisedScriptPurpose
AuthorisedScriptPurpose
Rewarding = AuthorisedScriptPurpose -> Either LiftError AuthorisedScriptPurpose
forall a b. b -> Either a b
Right AuthorisedScriptPurpose
Rewarding
| Bool
otherwise = LiftError -> Either LiftError AuthorisedScriptPurpose
forall a b. a -> Either a b
Left (Text -> LiftError
OtherLiftError Text
"Invalid Index")
instance PTryFrom PData (PAsData PAuthorisedScriptPurpose)
newtype PAuthorisedScriptProofIndex (s :: S)
= PAuthorisedScriptProofIndex
( Term
s
(PBuiltinPair (PAsData PAuthorisedScriptPurpose) (PAsData PInteger))
)
deriving stock ((forall x.
PAuthorisedScriptProofIndex s
-> Rep (PAuthorisedScriptProofIndex s) x)
-> (forall x.
Rep (PAuthorisedScriptProofIndex s) x
-> PAuthorisedScriptProofIndex s)
-> Generic (PAuthorisedScriptProofIndex s)
forall x.
Rep (PAuthorisedScriptProofIndex s) x
-> PAuthorisedScriptProofIndex s
forall x.
PAuthorisedScriptProofIndex s
-> Rep (PAuthorisedScriptProofIndex s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x.
Rep (PAuthorisedScriptProofIndex s) x
-> PAuthorisedScriptProofIndex s
forall (s :: S) x.
PAuthorisedScriptProofIndex s
-> Rep (PAuthorisedScriptProofIndex s) x
$cfrom :: forall (s :: S) x.
PAuthorisedScriptProofIndex s
-> Rep (PAuthorisedScriptProofIndex s) x
from :: forall x.
PAuthorisedScriptProofIndex s
-> Rep (PAuthorisedScriptProofIndex s) x
$cto :: forall (s :: S) x.
Rep (PAuthorisedScriptProofIndex s) x
-> PAuthorisedScriptProofIndex s
to :: forall x.
Rep (PAuthorisedScriptProofIndex s) x
-> PAuthorisedScriptProofIndex s
Generic)
deriving anyclass (All @[Type] (SListI @Type) (Code (PAuthorisedScriptProofIndex s))
All
@[Type] (SListI @Type) (Code (PAuthorisedScriptProofIndex s)) =>
(PAuthorisedScriptProofIndex s
-> Rep (PAuthorisedScriptProofIndex s))
-> (Rep (PAuthorisedScriptProofIndex s)
-> PAuthorisedScriptProofIndex s)
-> Generic (PAuthorisedScriptProofIndex s)
Rep (PAuthorisedScriptProofIndex s)
-> PAuthorisedScriptProofIndex s
PAuthorisedScriptProofIndex s
-> Rep (PAuthorisedScriptProofIndex s)
forall a.
All @[Type] (SListI @Type) (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (s :: S).
All @[Type] (SListI @Type) (Code (PAuthorisedScriptProofIndex s))
forall (s :: S).
Rep (PAuthorisedScriptProofIndex s)
-> PAuthorisedScriptProofIndex s
forall (s :: S).
PAuthorisedScriptProofIndex s
-> Rep (PAuthorisedScriptProofIndex s)
$cfrom :: forall (s :: S).
PAuthorisedScriptProofIndex s
-> Rep (PAuthorisedScriptProofIndex s)
from :: PAuthorisedScriptProofIndex s
-> Rep (PAuthorisedScriptProofIndex s)
$cto :: forall (s :: S).
Rep (PAuthorisedScriptProofIndex s)
-> PAuthorisedScriptProofIndex s
to :: Rep (PAuthorisedScriptProofIndex s)
-> PAuthorisedScriptProofIndex s
SOP.Generic, (forall (s :: S).
Term s (PAsData PAuthorisedScriptProofIndex)
-> Term s PAuthorisedScriptProofIndex)
-> (forall (s :: S).
Term s PAuthorisedScriptProofIndex -> Term s PData)
-> PIsData PAuthorisedScriptProofIndex
forall (s :: S).
Term s (PAsData PAuthorisedScriptProofIndex)
-> Term s PAuthorisedScriptProofIndex
forall (s :: S). Term s PAuthorisedScriptProofIndex -> Term s PData
forall (a :: S -> Type).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
$cpfromDataImpl :: forall (s :: S).
Term s (PAsData PAuthorisedScriptProofIndex)
-> Term s PAuthorisedScriptProofIndex
pfromDataImpl :: forall (s :: S).
Term s (PAsData PAuthorisedScriptProofIndex)
-> Term s PAuthorisedScriptProofIndex
$cpdataImpl :: forall (s :: S). Term s PAuthorisedScriptProofIndex -> Term s PData
pdataImpl :: forall (s :: S). Term s PAuthorisedScriptProofIndex -> Term s PData
PIsData)
deriving ((forall (s :: S).
PAuthorisedScriptProofIndex s
-> Term s (PInner PAuthorisedScriptProofIndex))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner PAuthorisedScriptProofIndex)
-> (PAuthorisedScriptProofIndex s -> Term s b) -> Term s b)
-> PlutusType PAuthorisedScriptProofIndex
forall (s :: S).
PAuthorisedScriptProofIndex s
-> Term s (PInner PAuthorisedScriptProofIndex)
forall (s :: S) (b :: S -> Type).
Term s (PInner PAuthorisedScriptProofIndex)
-> (PAuthorisedScriptProofIndex s -> Term s b) -> Term s b
forall (a :: S -> Type).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
$cpcon' :: forall (s :: S).
PAuthorisedScriptProofIndex s
-> Term s (PInner PAuthorisedScriptProofIndex)
pcon' :: forall (s :: S).
PAuthorisedScriptProofIndex s
-> Term s (PInner PAuthorisedScriptProofIndex)
$cpmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PAuthorisedScriptProofIndex)
-> (PAuthorisedScriptProofIndex s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PAuthorisedScriptProofIndex)
-> (PAuthorisedScriptProofIndex s -> Term s b) -> Term s b
PlutusType) via (DeriveNewtypePlutusType PAuthorisedScriptProofIndex)
deriving
(PlutusType PAuthorisedScriptProofIndex
AsHaskell PAuthorisedScriptProofIndex
-> PlutusRepr PAuthorisedScriptProofIndex
PlutusRepr PAuthorisedScriptProofIndex
-> Either LiftError (AsHaskell PAuthorisedScriptProofIndex)
PlutusType PAuthorisedScriptProofIndex =>
(AsHaskell PAuthorisedScriptProofIndex
-> PlutusRepr PAuthorisedScriptProofIndex)
-> (PlutusRepr PAuthorisedScriptProofIndex
-> Either LiftError (AsHaskell PAuthorisedScriptProofIndex))
-> (forall (s :: S).
PlutusRepr PAuthorisedScriptProofIndex
-> PLifted s PAuthorisedScriptProofIndex)
-> ((forall (s :: S). PLifted s PAuthorisedScriptProofIndex)
-> Either LiftError (PlutusRepr PAuthorisedScriptProofIndex))
-> PLiftable PAuthorisedScriptProofIndex
(forall (s :: S). PLifted s PAuthorisedScriptProofIndex)
-> Either LiftError (PlutusRepr PAuthorisedScriptProofIndex)
forall (s :: S).
PlutusRepr PAuthorisedScriptProofIndex
-> PLifted s PAuthorisedScriptProofIndex
forall (a :: S -> Type).
PlutusType a =>
(AsHaskell a -> PlutusRepr a)
-> (PlutusRepr a -> Either LiftError (AsHaskell a))
-> (forall (s :: S). PlutusRepr a -> PLifted s a)
-> ((forall (s :: S). PLifted s a)
-> Either LiftError (PlutusRepr a))
-> PLiftable a
$chaskToRepr :: AsHaskell PAuthorisedScriptProofIndex
-> PlutusRepr PAuthorisedScriptProofIndex
haskToRepr :: AsHaskell PAuthorisedScriptProofIndex
-> PlutusRepr PAuthorisedScriptProofIndex
$creprToHask :: PlutusRepr PAuthorisedScriptProofIndex
-> Either LiftError (AsHaskell PAuthorisedScriptProofIndex)
reprToHask :: PlutusRepr PAuthorisedScriptProofIndex
-> Either LiftError (AsHaskell PAuthorisedScriptProofIndex)
$creprToPlut :: forall (s :: S).
PlutusRepr PAuthorisedScriptProofIndex
-> PLifted s PAuthorisedScriptProofIndex
reprToPlut :: forall (s :: S).
PlutusRepr PAuthorisedScriptProofIndex
-> PLifted s PAuthorisedScriptProofIndex
$cplutToRepr :: (forall (s :: S). PLifted s PAuthorisedScriptProofIndex)
-> Either LiftError (PlutusRepr PAuthorisedScriptProofIndex)
plutToRepr :: (forall (s :: S). PLifted s PAuthorisedScriptProofIndex)
-> Either LiftError (PlutusRepr PAuthorisedScriptProofIndex)
PLiftable)
via (DeriveNewtypePLiftable PAuthorisedScriptProofIndex AuthorisedScriptProofIndex)
instance PTryFrom PData (PAsData PAuthorisedScriptProofIndex)
data PYieldingRedeemer (s :: S) = PYieldingRedeemer
{ forall (s :: S).
PYieldingRedeemer s -> Term s (PAsData PAuthorisedScriptIndex)
authorisedScriptIndex :: Term s (PAsData PAuthorisedScriptIndex)
, forall (s :: S).
PYieldingRedeemer s -> Term s (PAsData PAuthorisedScriptProofIndex)
authorisedScriptProofIndex :: Term s (PAsData PAuthorisedScriptProofIndex)
}
deriving stock ((forall x. PYieldingRedeemer s -> Rep (PYieldingRedeemer s) x)
-> (forall x. Rep (PYieldingRedeemer s) x -> PYieldingRedeemer s)
-> Generic (PYieldingRedeemer s)
forall x. Rep (PYieldingRedeemer s) x -> PYieldingRedeemer s
forall x. PYieldingRedeemer s -> Rep (PYieldingRedeemer s) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall (s :: S) x.
Rep (PYieldingRedeemer s) x -> PYieldingRedeemer s
forall (s :: S) x.
PYieldingRedeemer s -> Rep (PYieldingRedeemer s) x
$cfrom :: forall (s :: S) x.
PYieldingRedeemer s -> Rep (PYieldingRedeemer s) x
from :: forall x. PYieldingRedeemer s -> Rep (PYieldingRedeemer s) x
$cto :: forall (s :: S) x.
Rep (PYieldingRedeemer s) x -> PYieldingRedeemer s
to :: forall x. Rep (PYieldingRedeemer s) x -> PYieldingRedeemer s
Generic)
deriving anyclass (All @[Type] (SListI @Type) (Code (PYieldingRedeemer s))
All @[Type] (SListI @Type) (Code (PYieldingRedeemer s)) =>
(PYieldingRedeemer s -> Rep (PYieldingRedeemer s))
-> (Rep (PYieldingRedeemer s) -> PYieldingRedeemer s)
-> Generic (PYieldingRedeemer s)
Rep (PYieldingRedeemer s) -> PYieldingRedeemer s
PYieldingRedeemer s -> Rep (PYieldingRedeemer s)
forall a.
All @[Type] (SListI @Type) (Code a) =>
(a -> Rep a) -> (Rep a -> a) -> Generic a
forall (s :: S).
All @[Type] (SListI @Type) (Code (PYieldingRedeemer s))
forall (s :: S). Rep (PYieldingRedeemer s) -> PYieldingRedeemer s
forall (s :: S). PYieldingRedeemer s -> Rep (PYieldingRedeemer s)
$cfrom :: forall (s :: S). PYieldingRedeemer s -> Rep (PYieldingRedeemer s)
from :: PYieldingRedeemer s -> Rep (PYieldingRedeemer s)
$cto :: forall (s :: S). Rep (PYieldingRedeemer s) -> PYieldingRedeemer s
to :: Rep (PYieldingRedeemer s) -> PYieldingRedeemer s
SOP.Generic, (forall (s :: S).
Term s (PAsData PYieldingRedeemer) -> Term s PYieldingRedeemer)
-> (forall (s :: S). Term s PYieldingRedeemer -> Term s PData)
-> PIsData PYieldingRedeemer
forall (s :: S).
Term s (PAsData PYieldingRedeemer) -> Term s PYieldingRedeemer
forall (s :: S). Term s PYieldingRedeemer -> Term s PData
forall (a :: S -> Type).
(forall (s :: S). Term s (PAsData a) -> Term s a)
-> (forall (s :: S). Term s a -> Term s PData) -> PIsData a
$cpfromDataImpl :: forall (s :: S).
Term s (PAsData PYieldingRedeemer) -> Term s PYieldingRedeemer
pfromDataImpl :: forall (s :: S).
Term s (PAsData PYieldingRedeemer) -> Term s PYieldingRedeemer
$cpdataImpl :: forall (s :: S). Term s PYieldingRedeemer -> Term s PData
pdataImpl :: forall (s :: S). Term s PYieldingRedeemer -> Term s PData
PIsData)
deriving ((forall (s :: S).
PYieldingRedeemer s -> Term s (PInner PYieldingRedeemer))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner PYieldingRedeemer)
-> (PYieldingRedeemer s -> Term s b) -> Term s b)
-> PlutusType PYieldingRedeemer
forall (s :: S).
PYieldingRedeemer s -> Term s (PInner PYieldingRedeemer)
forall (s :: S) (b :: S -> Type).
Term s (PInner PYieldingRedeemer)
-> (PYieldingRedeemer s -> Term s b) -> Term s b
forall (a :: S -> Type).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: S -> Type).
Term s (PInner a) -> (a s -> Term s b) -> Term s b)
-> PlutusType a
$cpcon' :: forall (s :: S).
PYieldingRedeemer s -> Term s (PInner PYieldingRedeemer)
pcon' :: forall (s :: S).
PYieldingRedeemer s -> Term s (PInner PYieldingRedeemer)
$cpmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PYieldingRedeemer)
-> (PYieldingRedeemer s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: S -> Type).
Term s (PInner PYieldingRedeemer)
-> (PYieldingRedeemer s -> Term s b) -> Term s b
PlutusType) via (DeriveAsDataStruct PYieldingRedeemer)
deriving
(PlutusType PYieldingRedeemer
AsHaskell PYieldingRedeemer -> PlutusRepr PYieldingRedeemer
PlutusRepr PYieldingRedeemer
-> Either LiftError (AsHaskell PYieldingRedeemer)
PlutusType PYieldingRedeemer =>
(AsHaskell PYieldingRedeemer -> PlutusRepr PYieldingRedeemer)
-> (PlutusRepr PYieldingRedeemer
-> Either LiftError (AsHaskell PYieldingRedeemer))
-> (forall (s :: S).
PlutusRepr PYieldingRedeemer -> PLifted s PYieldingRedeemer)
-> ((forall (s :: S). PLifted s PYieldingRedeemer)
-> Either LiftError (PlutusRepr PYieldingRedeemer))
-> PLiftable PYieldingRedeemer
(forall (s :: S). PLifted s PYieldingRedeemer)
-> Either LiftError (PlutusRepr PYieldingRedeemer)
forall (s :: S).
PlutusRepr PYieldingRedeemer -> PLifted s PYieldingRedeemer
forall (a :: S -> Type).
PlutusType a =>
(AsHaskell a -> PlutusRepr a)
-> (PlutusRepr a -> Either LiftError (AsHaskell a))
-> (forall (s :: S). PlutusRepr a -> PLifted s a)
-> ((forall (s :: S). PLifted s a)
-> Either LiftError (PlutusRepr a))
-> PLiftable a
$chaskToRepr :: AsHaskell PYieldingRedeemer -> PlutusRepr PYieldingRedeemer
haskToRepr :: AsHaskell PYieldingRedeemer -> PlutusRepr PYieldingRedeemer
$creprToHask :: PlutusRepr PYieldingRedeemer
-> Either LiftError (AsHaskell PYieldingRedeemer)
reprToHask :: PlutusRepr PYieldingRedeemer
-> Either LiftError (AsHaskell PYieldingRedeemer)
$creprToPlut :: forall (s :: S).
PlutusRepr PYieldingRedeemer -> PLifted s PYieldingRedeemer
reprToPlut :: forall (s :: S).
PlutusRepr PYieldingRedeemer -> PLifted s PYieldingRedeemer
$cplutToRepr :: (forall (s :: S). PLifted s PYieldingRedeemer)
-> Either LiftError (PlutusRepr PYieldingRedeemer)
plutToRepr :: (forall (s :: S). PLifted s PYieldingRedeemer)
-> Either LiftError (PlutusRepr PYieldingRedeemer)
PLiftable)
via (DeriveDataPLiftable PYieldingRedeemer YieldingRedeemer)
instance PTryFrom PData (PAsData PYieldingRedeemer)
getAuthorisedScriptHash ::
forall (s :: S).
Term
s
( PCurrencySymbol
:--> PBuiltinList (PAsData PTxInInfo)
:--> PYieldingRedeemer
:--> PScriptHash
)
getAuthorisedScriptHash :: forall (s :: S).
Term
s
(PCurrencySymbol
:--> (PBuiltinList (PAsData PTxInInfo)
:--> (PYieldingRedeemer :--> PScriptHash)))
getAuthorisedScriptHash = (forall (s :: S).
Term
s
(PCurrencySymbol
:--> (PBuiltinList (PAsData PTxInInfo)
:--> (PYieldingRedeemer :--> PScriptHash))))
-> Term
s
(PCurrencySymbol
:--> (PBuiltinList (PAsData PTxInInfo)
:--> (PYieldingRedeemer :--> PScriptHash)))
forall (a :: S -> Type) (s :: S).
HasCallStack =>
ClosedTerm a -> Term s a
phoistAcyclic ((forall (s :: S).
Term
s
(PCurrencySymbol
:--> (PBuiltinList (PAsData PTxInInfo)
:--> (PYieldingRedeemer :--> PScriptHash))))
-> Term
s
(PCurrencySymbol
:--> (PBuiltinList (PAsData PTxInInfo)
:--> (PYieldingRedeemer :--> PScriptHash))))
-> (forall (s :: S).
Term
s
(PCurrencySymbol
:--> (PBuiltinList (PAsData PTxInInfo)
:--> (PYieldingRedeemer :--> PScriptHash))))
-> Term
s
(PCurrencySymbol
:--> (PBuiltinList (PAsData PTxInInfo)
:--> (PYieldingRedeemer :--> PScriptHash)))
forall a b. (a -> b) -> a -> b
$
(Term s PCurrencySymbol
-> Term s (PBuiltinList (PAsData PTxInInfo))
-> Term s PYieldingRedeemer
-> Term s PScriptHash)
-> Term
s
(PCurrencySymbol
:--> (PBuiltinList (PAsData PTxInInfo)
:--> (PYieldingRedeemer :--> PScriptHash)))
forall a (b :: S -> Type) (s :: S) (c :: S -> Type).
(PLamN a b s, HasCallStack) =>
(Term s c -> a) -> Term s (c :--> b)
forall (c :: S -> Type).
HasCallStack =>
(Term s c
-> Term s (PBuiltinList (PAsData PTxInInfo))
-> Term s PYieldingRedeemer
-> Term s PScriptHash)
-> Term
s
(c
:--> (PBuiltinList (PAsData PTxInInfo)
:--> (PYieldingRedeemer :--> PScriptHash)))
plam ((Term s PCurrencySymbol
-> Term s (PBuiltinList (PAsData PTxInInfo))
-> Term s PYieldingRedeemer
-> Term s PScriptHash)
-> Term
s
(PCurrencySymbol
:--> (PBuiltinList (PAsData PTxInInfo)
:--> (PYieldingRedeemer :--> PScriptHash))))
-> (Term s PCurrencySymbol
-> Term s (PBuiltinList (PAsData PTxInInfo))
-> Term s PYieldingRedeemer
-> Term s PScriptHash)
-> Term
s
(PCurrencySymbol
:--> (PBuiltinList (PAsData PTxInInfo)
:--> (PYieldingRedeemer :--> PScriptHash)))
forall a b. (a -> b) -> a -> b
$
\Term s PCurrencySymbol
psymbol Term s (PBuiltinList (PAsData PTxInInfo))
txInfoRefInputs Term s PYieldingRedeemer
redeemer -> TermCont @PScriptHash s (Term s PScriptHash) -> Term s PScriptHash
forall (a :: S -> Type) (s :: S).
TermCont @a s (Term s a) -> Term s a
unTermCont (TermCont @PScriptHash s (Term s PScriptHash)
-> Term s PScriptHash)
-> TermCont @PScriptHash s (Term s PScriptHash)
-> Term s PScriptHash
forall a b. (a -> b) -> a -> b
$ do
PYieldingRedeemer Term s (PAsData PAuthorisedScriptIndex)
authorisedScriptIndex Term s (PAsData PAuthorisedScriptProofIndex)
_ <- Term s PYieldingRedeemer
-> TermCont @PScriptHash s (PYieldingRedeemer s)
forall {r :: S -> Type} (a :: S -> Type) (s :: S).
PlutusType a =>
Term s a -> TermCont @r s (a s)
pmatchC Term s PYieldingRedeemer
redeemer
let autorisedScriptRefUTxO :: Term s (PAsData PTxInInfo)
autorisedScriptRefUTxO =
Term s (PBuiltinList (PAsData PTxInInfo))
txInfoRefInputs
#!! pto (pfromData authorisedScriptIndex)
PTxInInfo s
scriptRefFields <- Term s PTxInInfo -> TermCont @PScriptHash s (PTxInInfo s)
forall {r :: S -> Type} (a :: S -> Type) (s :: S).
PlutusType a =>
Term s a -> TermCont @r s (a s)
pmatchC (Term s PTxInInfo -> TermCont @PScriptHash s (PTxInInfo s))
-> Term s PTxInInfo -> TermCont @PScriptHash s (PTxInInfo s)
forall a b. (a -> b) -> a -> b
$ Term s (PAsData PTxInInfo) -> Term s PTxInInfo
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData PTxInInfo)
autorisedScriptRefUTxO
Term s PTxOut
resolved' <- Term s PTxOut -> TermCont @PScriptHash s (Term s PTxOut)
forall {r :: S -> Type} (s :: S) (a :: S -> Type).
Term s a -> TermCont @r s (Term s a)
pletC (Term s PTxOut -> TermCont @PScriptHash s (Term s PTxOut))
-> Term s PTxOut -> TermCont @PScriptHash s (Term s PTxOut)
forall a b. (a -> b) -> a -> b
$ PTxInInfo s -> Term s PTxOut
forall (s :: S). PTxInInfo s -> Term s PTxOut
ptxInInfo'resolved PTxInInfo s
scriptRefFields
PTxOut s
resolved <- Term s PTxOut -> TermCont @PScriptHash s (PTxOut s)
forall {r :: S -> Type} (a :: S -> Type) (s :: S).
PlutusType a =>
Term s a -> TermCont @r s (a s)
pmatchC Term s PTxOut
resolved'
let
value :: Term s (PAsData (PValue 'Sorted 'Positive))
value = PTxOut s -> Term s (PAsData (PValue 'Sorted 'Positive))
forall (s :: S).
PTxOut s -> Term s (PAsData (PValue 'Sorted 'Positive))
ptxOut'value PTxOut s
resolved
referenceScript :: Term s (PMaybeData PScriptHash)
referenceScript = PTxOut s -> Term s (PMaybeData PScriptHash)
forall (s :: S). PTxOut s -> Term s (PMaybeData PScriptHash)
ptxOut'referenceScript PTxOut s
resolved
Term s PScriptHash -> TermCont @PScriptHash s (Term s PScriptHash)
forall a. a -> TermCont @PScriptHash s a
forall (f :: Type -> Type) a. Applicative f => a -> f a
pure (Term s PScriptHash
-> TermCont @PScriptHash s (Term s PScriptHash))
-> Term s PScriptHash
-> TermCont @PScriptHash s (Term s PScriptHash)
forall a b. (a -> b) -> a -> b
$
Term s PBool
-> Term s PScriptHash -> Term s PScriptHash -> Term s PScriptHash
forall (a :: S -> Type) (s :: S).
Term s PBool -> Term s a -> Term s a -> Term s a
pif
(Term
s
(PCurrencySymbol
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PBool))
forall (k :: S -> Type) (s :: S) (any :: KeyGuarantees)
(v :: S -> Type).
PIsData k =>
Term s (k :--> (PMap any k v :--> PBool))
pmember Term
s
(PCurrencySymbol
:--> (PMap
'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PBool))
-> Term s PCurrencySymbol
-> Term
s
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PBool)
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s PCurrencySymbol
psymbol Term
s
(PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger)
:--> PBool)
-> Term
s (PMap 'Sorted PCurrencySymbol (PMap 'Sorted PTokenName PInteger))
-> Term s PBool
forall (s :: S) (a :: S -> Type) (b :: S -> Type).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PValue 'Sorted 'Positive)
-> Term s (PInner (PValue 'Sorted 'Positive))
forall (s :: S) (a :: S -> Type). Term s a -> Term s (PInner a)
pto (Term s (PAsData (PValue 'Sorted 'Positive))
-> Term s (PValue 'Sorted 'Positive)
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData (PValue 'Sorted 'Positive))
value))
( Term s (PMaybeData PScriptHash)
-> (PMaybeData PScriptHash s -> Term s PScriptHash)
-> Term s PScriptHash
forall (a :: S -> Type) (s :: S) (b :: S -> Type).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch Term s (PMaybeData PScriptHash)
referenceScript ((PMaybeData PScriptHash s -> Term s PScriptHash)
-> Term s PScriptHash)
-> (PMaybeData PScriptHash s -> Term s PScriptHash)
-> Term s PScriptHash
forall a b. (a -> b) -> a -> b
$ \case
PDJust Term s (PAsData PScriptHash)
autorisedScript -> Term s (PAsData PScriptHash) -> Term s PScriptHash
forall (a :: S -> Type) (s :: S).
PIsData a =>
Term s (PAsData a) -> Term s a
pfromData Term s (PAsData PScriptHash)
autorisedScript
PMaybeData PScriptHash s
PDNothing ->
( Term s PString -> Term s PScriptHash
forall (a :: S -> Type) (s :: S). Term s PString -> Term s a
ptraceInfoError
Term s PString
"getAuthorisedScriptHash: Reference input does not contain reference script"
)
)
( Term s PString -> Term s PScriptHash
forall (a :: S -> Type) (s :: S). Term s PString -> Term s a
ptraceInfoError
Term s PString
"getAuthorisedScriptHash: Reference input does not contain AuthorisedScriptsSTCS"
)