{-# OPTIONS_GHC -fno-warn-orphans #-}
module Cardano.YTxP.Control.Yielding (
getAuthorisedScriptHash,
PAuthorisedScriptPurpose (PMinting, PSpending, PRewarding),
PYieldingRedeemer,
)
where
import Cardano.YTxP.Control.Vendored (DerivePConstantViaEnum (DerivePConstantEnum), PlutusTypeEnumData)
import Cardano.YTxP.SDK.Redeemers (
AuthorisedScriptIndex (AuthorisedScriptIndex),
AuthorisedScriptProofIndex (AuthorisedScriptProofIndex),
AuthorisedScriptPurpose,
YieldingRedeemer,
)
import Plutarch.DataRepr (DerivePConstantViaData (DerivePConstantViaData), PDataFields)
import Plutarch.LedgerApi.Utils (PMaybeData (PDJust, PDNothing))
import Plutarch.LedgerApi.V2 (
PCurrencySymbol,
PScriptHash,
PTxInInfo,
)
import Plutarch.Lift (
DerivePConstantViaNewtype (DerivePConstantViaNewtype),
PConstantDecl,
PLifted,
PUnsafeLiftDecl,
)
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 ((forall (s :: S).
PAuthorisedScriptIndex s -> Term s (PInner PAuthorisedScriptIndex))
-> (forall (s :: S) (b :: PType).
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 :: PType).
Term s (PInner PAuthorisedScriptIndex)
-> (PAuthorisedScriptIndex s -> Term s b) -> Term s b
forall (a :: PType).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: PType).
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 :: PType).
Term s (PInner PAuthorisedScriptIndex)
-> (PAuthorisedScriptIndex s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: PType).
Term s (PInner PAuthorisedScriptIndex)
-> (PAuthorisedScriptIndex s -> Term s b) -> Term s b
PlutusType, (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 :: PType).
(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)
instance DerivePlutusType PAuthorisedScriptIndex where
type DPTStrat _ = PlutusTypeNewtype
instance PTryFrom PData (PAsData PAuthorisedScriptIndex)
instance PUnsafeLiftDecl PAuthorisedScriptIndex where
type PLifted PAuthorisedScriptIndex = AuthorisedScriptIndex
deriving via
(DerivePConstantViaNewtype AuthorisedScriptIndex PAuthorisedScriptIndex PInteger)
instance
(PConstantDecl AuthorisedScriptIndex)
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 ((forall (s :: S).
PAuthorisedScriptPurpose s
-> Term s (PInner PAuthorisedScriptPurpose))
-> (forall (s :: S) (b :: PType).
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 :: PType).
Term s (PInner PAuthorisedScriptPurpose)
-> (PAuthorisedScriptPurpose s -> Term s b) -> Term s b
forall (a :: PType).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: PType).
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 :: PType).
Term s (PInner PAuthorisedScriptPurpose)
-> (PAuthorisedScriptPurpose s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: PType).
Term s (PInner PAuthorisedScriptPurpose)
-> (PAuthorisedScriptPurpose s -> Term s b) -> Term s b
PlutusType, (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 :: PType).
(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 :: PType).
(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)
instance DerivePlutusType PAuthorisedScriptPurpose where
type DPTStrat _ = PlutusTypeEnumData
instance PTryFrom PData (PAsData PAuthorisedScriptPurpose)
instance PUnsafeLiftDecl PAuthorisedScriptPurpose where
type PLifted PAuthorisedScriptPurpose = AuthorisedScriptPurpose
deriving via
(DerivePConstantViaEnum AuthorisedScriptPurpose PAuthorisedScriptPurpose)
instance
(PConstantDecl AuthorisedScriptPurpose)
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 ((forall (s :: S).
PAuthorisedScriptProofIndex s
-> Term s (PInner PAuthorisedScriptProofIndex))
-> (forall (s :: S) (b :: PType).
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 :: PType).
Term s (PInner PAuthorisedScriptProofIndex)
-> (PAuthorisedScriptProofIndex s -> Term s b) -> Term s b
forall (a :: PType).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: PType).
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 :: PType).
Term s (PInner PAuthorisedScriptProofIndex)
-> (PAuthorisedScriptProofIndex s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: PType).
Term s (PInner PAuthorisedScriptProofIndex)
-> (PAuthorisedScriptProofIndex s -> Term s b) -> Term s b
PlutusType, (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 :: PType).
(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)
instance DerivePlutusType PAuthorisedScriptProofIndex where
type DPTStrat _ = PlutusTypeNewtype
instance PTryFrom PData (PAsData PAuthorisedScriptProofIndex)
instance PUnsafeLiftDecl PAuthorisedScriptProofIndex where
type PLifted PAuthorisedScriptProofIndex = AuthorisedScriptProofIndex
deriving via
(DerivePConstantViaNewtype AuthorisedScriptProofIndex PAuthorisedScriptProofIndex (PBuiltinPair PAuthorisedScriptPurpose PInteger))
instance
(PConstantDecl AuthorisedScriptProofIndex)
newtype PYieldingRedeemer (s :: S)
= PYieldingRedeemer
( Term
s
( PDataRecord
'[ "authorisedScriptIndex" ':= PAuthorisedScriptIndex
, "authorisedScriptProofIndex" ':= 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 ((forall (s :: S).
PYieldingRedeemer s -> Term s (PInner PYieldingRedeemer))
-> (forall (s :: S) (b :: PType).
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 :: PType).
Term s (PInner PYieldingRedeemer)
-> (PYieldingRedeemer s -> Term s b) -> Term s b
forall (a :: PType).
(forall (s :: S). a s -> Term s (PInner a))
-> (forall (s :: S) (b :: PType).
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 :: PType).
Term s (PInner PYieldingRedeemer)
-> (PYieldingRedeemer s -> Term s b) -> Term s b
pmatch' :: forall (s :: S) (b :: PType).
Term s (PInner PYieldingRedeemer)
-> (PYieldingRedeemer s -> Term s b) -> Term s b
PlutusType, (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 :: PType).
(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, (forall (s :: S).
Term s PYieldingRedeemer
-> Term s (PDataRecord (PFields PYieldingRedeemer)))
-> PDataFields PYieldingRedeemer
forall (s :: S).
Term s PYieldingRedeemer
-> Term s (PDataRecord (PFields PYieldingRedeemer))
forall (a :: PType).
(forall (s :: S). Term s a -> Term s (PDataRecord (PFields a)))
-> PDataFields a
$cptoFields :: forall (s :: S).
Term s PYieldingRedeemer
-> Term s (PDataRecord (PFields PYieldingRedeemer))
ptoFields :: forall (s :: S).
Term s PYieldingRedeemer
-> Term s (PDataRecord (PFields PYieldingRedeemer))
PDataFields)
instance DerivePlutusType PYieldingRedeemer where
type DPTStrat _ = PlutusTypeData
instance PTryFrom PData (PAsData PYieldingRedeemer)
instance PUnsafeLiftDecl PYieldingRedeemer where
type PLifted PYieldingRedeemer = YieldingRedeemer
deriving via
(DerivePConstantViaData YieldingRedeemer PYieldingRedeemer)
instance
(PConstantDecl YieldingRedeemer)
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 :: PType) (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 :: 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 (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 :: PType) (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
HRec
(BoundTerms
(PFields PYieldingRedeemer)
(Bindings
(PFields PYieldingRedeemer)
((':) @Symbol "authorisedScriptIndex" ('[] @Symbol)))
s)
yieldingRedeemer <-
forall (fs :: [Symbol]) (a :: PType) (s :: S) (b :: PType)
(ps :: [PLabeledType]) (bs :: [ToBind]).
(PDataFields a,
(ps :: [PLabeledType]) ~ (PFields a :: [PLabeledType]),
(bs :: [ToBind]) ~ (Bindings ps fs :: [ToBind]),
BindFields ps bs) =>
Term s a -> TermCont @b s (HRec (BoundTerms ps bs s))
pletFieldsC @'["authorisedScriptIndex"] Term s PYieldingRedeemer
redeemer
let autorisedScriptRefUTxO :: Term s (PAsData PTxInInfo)
autorisedScriptRefUTxO =
Term s (PBuiltinList (PAsData PTxInInfo))
txInfoRefInputs
#!! pto (pfromData $ getField @"authorisedScriptIndex" yieldingRedeemer)
output :: Term s (PAsData PTxOut)
output = forall (name :: Symbol) (b :: PType) (p :: PType) (s :: S)
(a :: PType) (as :: [PLabeledType]) (n :: Nat).
(PDataFields p,
(as :: [PLabeledType]) ~ (PFields p :: [PLabeledType]),
(n :: Nat) ~ (PLabelIndex name as :: Nat), KnownNat n,
(a :: PType) ~ (PUnLabel (IndexList @PLabeledType n as) :: PType),
PFromDataable a b) =>
Term s (p :--> b)
pfield @"resolved" Term s (PAsData PTxInInfo :--> PAsData PTxOut)
-> Term s (PAsData PTxInInfo) -> Term s (PAsData PTxOut)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PAsData PTxInInfo)
autorisedScriptRefUTxO
value :: Term s (PAsData (PValue 'Sorted 'Positive))
value = forall (name :: Symbol) (b :: PType) (p :: PType) (s :: S)
(a :: PType) (as :: [PLabeledType]) (n :: Nat).
(PDataFields p,
(as :: [PLabeledType]) ~ (PFields p :: [PLabeledType]),
(n :: Nat) ~ (PLabelIndex name as :: Nat), KnownNat n,
(a :: PType) ~ (PUnLabel (IndexList @PLabeledType n as) :: PType),
PFromDataable a b) =>
Term s (p :--> b)
pfield @"value" Term s (PAsData PTxOut :--> PAsData (PValue 'Sorted 'Positive))
-> Term s (PAsData PTxOut)
-> Term s (PAsData (PValue 'Sorted 'Positive))
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PAsData PTxOut)
output
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 (s :: S) (a :: PType).
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 :: PType) (s :: S) (any :: KeyGuarantees) (v :: PType).
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 :: PType) (b :: PType).
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 :: PType) (b :: PType).
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 :: PType). Term s a -> Term s (PInner a)
pto (Term s (PAsData (PValue 'Sorted 'Positive))
-> Term s (PValue 'Sorted 'Positive)
forall (a :: PType) (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 :: PType) (s :: S) (b :: PType).
PlutusType a =>
Term s a -> (a s -> Term s b) -> Term s b
pmatch (forall (name :: Symbol) (b :: PType) (p :: PType) (s :: S)
(a :: PType) (as :: [PLabeledType]) (n :: Nat).
(PDataFields p,
(as :: [PLabeledType]) ~ (PFields p :: [PLabeledType]),
(n :: Nat) ~ (PLabelIndex name as :: Nat), KnownNat n,
(a :: PType) ~ (PUnLabel (IndexList @PLabeledType n as) :: PType),
PFromDataable a b) =>
Term s (p :--> b)
pfield @"referenceScript" Term s (PAsData PTxOut :--> PMaybeData PScriptHash)
-> Term s (PAsData PTxOut) -> Term s (PMaybeData PScriptHash)
forall (s :: S) (a :: PType) (b :: PType).
Term s (a :--> b) -> Term s a -> Term s b
# Term s (PAsData PTxOut)
output) ((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 ((forall (name :: Symbol) (b :: PType) (p :: PType) (s :: S)
(a :: PType) (as :: [PLabeledType]) (n :: Nat).
(PDataFields p,
(as :: [PLabeledType]) ~ (PFields p :: [PLabeledType]),
(n :: Nat) ~ (PLabelIndex name as :: Nat), KnownNat n,
(a :: PType) ~ (PUnLabel (IndexList @PLabeledType n as) :: PType),
PFromDataable a b) =>
Term s (p :--> b)
pfield @"_0" #) -> Term s PScriptHash
autorisedScript) -> Term s PScriptHash
autorisedScript
PDNothing Term s (PDataRecord ('[] @PLabeledType))
_ -> (Term s PString -> Term s PScriptHash
forall (a :: PType) (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 :: PType) (s :: S). Term s PString -> Term s a
ptraceInfoError Term s PString
"getAuthorisedScriptHash: Reference input does not contain AuthorisedScriptsSTCS")