{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingVia #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE ViewPatterns #-}
{-# OPTIONS_GHC -Wno-simplifiable-class-constraints #-}
{-# OPTIONS_GHC -fexpose-all-unfoldings #-}
{-# OPTIONS_GHC -fno-omit-interface-pragmas #-}
{-# OPTIONS_GHC -fno-specialise #-}
{-# OPTIONS_GHC -fno-strictness #-}
module PlutusLedgerApi.V3.Data.Contexts (
ColdCommitteeCredential (..),
HotCommitteeCredential (..),
DRepCredential (..),
DRep,
pattern DRep,
pattern DRepAlwaysAbstain,
pattern DRepAlwaysNoConfidence,
Delegatee,
pattern DelegStake,
pattern DelegVote,
pattern DelegStakeVote,
TxCert,
pattern TxCertRegStaking,
pattern TxCertUnRegStaking,
pattern TxCertDelegStaking,
pattern TxCertRegDeleg,
pattern TxCertRegDRep,
pattern TxCertUpdateDRep,
pattern TxCertUnRegDRep,
pattern TxCertPoolRegister,
pattern TxCertPoolRetire,
pattern TxCertAuthHotCommittee,
pattern TxCertResignColdCommittee,
Voter,
pattern CommitteeVoter,
pattern DRepVoter,
pattern StakePoolVoter,
Vote,
pattern VoteNo,
pattern VoteYes,
pattern Abstain,
GovernanceActionId,
pattern GovernanceActionId,
gaidTxId,
gaidGovActionIx,
Committee,
pattern Committee,
committeeMembers,
committeeQuorum,
Constitution (..),
ProtocolVersion,
pattern ProtocolVersion,
pvMajor,
pvMinor,
ChangedParameters (..),
GovernanceAction,
pattern ParameterChange,
pattern HardForkInitiation,
pattern TreasuryWithdrawals,
pattern NoConfidence,
pattern UpdateCommittee,
pattern NewConstitution,
pattern InfoAction,
ProposalProcedure,
pattern ProposalProcedure,
ppDeposit,
ppReturnAddr,
ppGovernanceAction,
ScriptPurpose,
pattern Minting,
pattern Spending,
pattern Rewarding,
pattern Certifying,
pattern Voting,
pattern Proposing,
ScriptInfo,
pattern MintingScript,
pattern SpendingScript,
pattern RewardingScript,
pattern CertifyingScript,
pattern VotingScript,
pattern ProposingScript,
TxInInfo,
pattern TxInInfo,
txInInfoOutRef,
txInInfoResolved,
TxInfo,
pattern TxInfo,
txInfoInputs,
txInfoReferenceInputs,
txInfoOutputs,
txInfoFee,
txInfoMint,
txInfoTxCerts,
txInfoWdrl,
txInfoValidRange,
txInfoSignatories,
txInfoRedeemers,
txInfoData,
txInfoId,
txInfoVotes,
txInfoProposalProcedures,
txInfoCurrentTreasuryAmount,
txInfoTreasuryDonation,
ScriptContext,
pattern ScriptContext,
scriptContextTxInfo,
scriptContextRedeemer,
scriptContextScriptInfo,
findOwnInput,
findDatum,
findDatumHash,
findTxInByTxOutRef,
findContinuingOutputs,
getContinuingOutputs,
txSignedBy,
pubKeyOutputsAt,
valuePaidTo,
valueSpent,
valueProduced,
ownCurrencySymbol,
spendsOutput,
) where
import GHC.Generics (Generic)
import Prettyprinter (nest, vsep, (<+>))
import Prettyprinter.Extras
import PlutusLedgerApi.Data.V2 qualified as V2
import PlutusLedgerApi.V3.Data.Tx qualified as V3
import PlutusTx qualified
import PlutusTx.AsData qualified as PlutusTx
import PlutusTx.Data.AssocMap
import PlutusTx.Data.List (List)
import PlutusTx.Data.List qualified as Data.List
import PlutusTx.Prelude qualified as PlutusTx
import PlutusTx.Ratio (Rational)
import Prelude qualified as Haskell
newtype ColdCommitteeCredential = ColdCommitteeCredential V2.Credential
deriving stock ((forall x.
ColdCommitteeCredential -> Rep ColdCommitteeCredential x)
-> (forall x.
Rep ColdCommitteeCredential x -> ColdCommitteeCredential)
-> Generic ColdCommitteeCredential
forall x. Rep ColdCommitteeCredential x -> ColdCommitteeCredential
forall x. ColdCommitteeCredential -> Rep ColdCommitteeCredential x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ColdCommitteeCredential -> Rep ColdCommitteeCredential x
from :: forall x. ColdCommitteeCredential -> Rep ColdCommitteeCredential x
$cto :: forall x. Rep ColdCommitteeCredential x -> ColdCommitteeCredential
to :: forall x. Rep ColdCommitteeCredential x -> ColdCommitteeCredential
Generic)
deriving ((forall ann. ColdCommitteeCredential -> Doc ann)
-> (forall ann. [ColdCommitteeCredential] -> Doc ann)
-> Pretty ColdCommitteeCredential
forall ann. [ColdCommitteeCredential] -> Doc ann
forall ann. ColdCommitteeCredential -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. ColdCommitteeCredential -> Doc ann
pretty :: forall ann. ColdCommitteeCredential -> Doc ann
$cprettyList :: forall ann. [ColdCommitteeCredential] -> Doc ann
prettyList :: forall ann. [ColdCommitteeCredential] -> Doc ann
Pretty) via (PrettyShow ColdCommitteeCredential)
deriving newtype
( ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
(ColdCommitteeCredential -> ColdCommitteeCredential -> Bool)
-> (ColdCommitteeCredential -> ColdCommitteeCredential -> Bool)
-> Eq ColdCommitteeCredential
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
== :: ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
$c/= :: ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
/= :: ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
Haskell.Eq
, Int -> ColdCommitteeCredential -> ShowS
[ColdCommitteeCredential] -> ShowS
ColdCommitteeCredential -> String
(Int -> ColdCommitteeCredential -> ShowS)
-> (ColdCommitteeCredential -> String)
-> ([ColdCommitteeCredential] -> ShowS)
-> Show ColdCommitteeCredential
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ColdCommitteeCredential -> ShowS
showsPrec :: Int -> ColdCommitteeCredential -> ShowS
$cshow :: ColdCommitteeCredential -> String
show :: ColdCommitteeCredential -> String
$cshowList :: [ColdCommitteeCredential] -> ShowS
showList :: [ColdCommitteeCredential] -> ShowS
Haskell.Show
, ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
(ColdCommitteeCredential -> ColdCommitteeCredential -> Bool)
-> Eq ColdCommitteeCredential
forall a. (a -> a -> Bool) -> Eq a
$c== :: ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
== :: ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
PlutusTx.Eq
, ColdCommitteeCredential -> BuiltinData
(ColdCommitteeCredential -> BuiltinData)
-> ToData ColdCommitteeCredential
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: ColdCommitteeCredential -> BuiltinData
toBuiltinData :: ColdCommitteeCredential -> BuiltinData
PlutusTx.ToData
, BuiltinData -> Maybe ColdCommitteeCredential
(BuiltinData -> Maybe ColdCommitteeCredential)
-> FromData ColdCommitteeCredential
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe ColdCommitteeCredential
fromBuiltinData :: BuiltinData -> Maybe ColdCommitteeCredential
PlutusTx.FromData
, BuiltinData -> ColdCommitteeCredential
(BuiltinData -> ColdCommitteeCredential)
-> UnsafeFromData ColdCommitteeCredential
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> ColdCommitteeCredential
unsafeFromBuiltinData :: BuiltinData -> ColdCommitteeCredential
PlutusTx.UnsafeFromData
)
PlutusTx.makeLift ''ColdCommitteeCredential
newtype HotCommitteeCredential = HotCommitteeCredential V2.Credential
deriving stock ((forall x. HotCommitteeCredential -> Rep HotCommitteeCredential x)
-> (forall x.
Rep HotCommitteeCredential x -> HotCommitteeCredential)
-> Generic HotCommitteeCredential
forall x. Rep HotCommitteeCredential x -> HotCommitteeCredential
forall x. HotCommitteeCredential -> Rep HotCommitteeCredential x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. HotCommitteeCredential -> Rep HotCommitteeCredential x
from :: forall x. HotCommitteeCredential -> Rep HotCommitteeCredential x
$cto :: forall x. Rep HotCommitteeCredential x -> HotCommitteeCredential
to :: forall x. Rep HotCommitteeCredential x -> HotCommitteeCredential
Generic)
deriving ((forall ann. HotCommitteeCredential -> Doc ann)
-> (forall ann. [HotCommitteeCredential] -> Doc ann)
-> Pretty HotCommitteeCredential
forall ann. [HotCommitteeCredential] -> Doc ann
forall ann. HotCommitteeCredential -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. HotCommitteeCredential -> Doc ann
pretty :: forall ann. HotCommitteeCredential -> Doc ann
$cprettyList :: forall ann. [HotCommitteeCredential] -> Doc ann
prettyList :: forall ann. [HotCommitteeCredential] -> Doc ann
Pretty) via (PrettyShow HotCommitteeCredential)
deriving newtype
( HotCommitteeCredential -> HotCommitteeCredential -> Bool
(HotCommitteeCredential -> HotCommitteeCredential -> Bool)
-> (HotCommitteeCredential -> HotCommitteeCredential -> Bool)
-> Eq HotCommitteeCredential
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: HotCommitteeCredential -> HotCommitteeCredential -> Bool
== :: HotCommitteeCredential -> HotCommitteeCredential -> Bool
$c/= :: HotCommitteeCredential -> HotCommitteeCredential -> Bool
/= :: HotCommitteeCredential -> HotCommitteeCredential -> Bool
Haskell.Eq
, Int -> HotCommitteeCredential -> ShowS
[HotCommitteeCredential] -> ShowS
HotCommitteeCredential -> String
(Int -> HotCommitteeCredential -> ShowS)
-> (HotCommitteeCredential -> String)
-> ([HotCommitteeCredential] -> ShowS)
-> Show HotCommitteeCredential
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> HotCommitteeCredential -> ShowS
showsPrec :: Int -> HotCommitteeCredential -> ShowS
$cshow :: HotCommitteeCredential -> String
show :: HotCommitteeCredential -> String
$cshowList :: [HotCommitteeCredential] -> ShowS
showList :: [HotCommitteeCredential] -> ShowS
Haskell.Show
, HotCommitteeCredential -> HotCommitteeCredential -> Bool
(HotCommitteeCredential -> HotCommitteeCredential -> Bool)
-> Eq HotCommitteeCredential
forall a. (a -> a -> Bool) -> Eq a
$c== :: HotCommitteeCredential -> HotCommitteeCredential -> Bool
== :: HotCommitteeCredential -> HotCommitteeCredential -> Bool
PlutusTx.Eq
, HotCommitteeCredential -> BuiltinData
(HotCommitteeCredential -> BuiltinData)
-> ToData HotCommitteeCredential
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: HotCommitteeCredential -> BuiltinData
toBuiltinData :: HotCommitteeCredential -> BuiltinData
PlutusTx.ToData
, BuiltinData -> Maybe HotCommitteeCredential
(BuiltinData -> Maybe HotCommitteeCredential)
-> FromData HotCommitteeCredential
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe HotCommitteeCredential
fromBuiltinData :: BuiltinData -> Maybe HotCommitteeCredential
PlutusTx.FromData
, BuiltinData -> HotCommitteeCredential
(BuiltinData -> HotCommitteeCredential)
-> UnsafeFromData HotCommitteeCredential
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> HotCommitteeCredential
unsafeFromBuiltinData :: BuiltinData -> HotCommitteeCredential
PlutusTx.UnsafeFromData
)
PlutusTx.makeLift ''HotCommitteeCredential
newtype DRepCredential = DRepCredential V2.Credential
deriving stock ((forall x. DRepCredential -> Rep DRepCredential x)
-> (forall x. Rep DRepCredential x -> DRepCredential)
-> Generic DRepCredential
forall x. Rep DRepCredential x -> DRepCredential
forall x. DRepCredential -> Rep DRepCredential x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. DRepCredential -> Rep DRepCredential x
from :: forall x. DRepCredential -> Rep DRepCredential x
$cto :: forall x. Rep DRepCredential x -> DRepCredential
to :: forall x. Rep DRepCredential x -> DRepCredential
Generic)
deriving ((forall ann. DRepCredential -> Doc ann)
-> (forall ann. [DRepCredential] -> Doc ann)
-> Pretty DRepCredential
forall ann. [DRepCredential] -> Doc ann
forall ann. DRepCredential -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. DRepCredential -> Doc ann
pretty :: forall ann. DRepCredential -> Doc ann
$cprettyList :: forall ann. [DRepCredential] -> Doc ann
prettyList :: forall ann. [DRepCredential] -> Doc ann
Pretty) via (PrettyShow DRepCredential)
deriving newtype
( DRepCredential -> DRepCredential -> Bool
(DRepCredential -> DRepCredential -> Bool)
-> (DRepCredential -> DRepCredential -> Bool) -> Eq DRepCredential
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DRepCredential -> DRepCredential -> Bool
== :: DRepCredential -> DRepCredential -> Bool
$c/= :: DRepCredential -> DRepCredential -> Bool
/= :: DRepCredential -> DRepCredential -> Bool
Haskell.Eq
, Int -> DRepCredential -> ShowS
[DRepCredential] -> ShowS
DRepCredential -> String
(Int -> DRepCredential -> ShowS)
-> (DRepCredential -> String)
-> ([DRepCredential] -> ShowS)
-> Show DRepCredential
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DRepCredential -> ShowS
showsPrec :: Int -> DRepCredential -> ShowS
$cshow :: DRepCredential -> String
show :: DRepCredential -> String
$cshowList :: [DRepCredential] -> ShowS
showList :: [DRepCredential] -> ShowS
Haskell.Show
, DRepCredential -> DRepCredential -> Bool
(DRepCredential -> DRepCredential -> Bool) -> Eq DRepCredential
forall a. (a -> a -> Bool) -> Eq a
$c== :: DRepCredential -> DRepCredential -> Bool
== :: DRepCredential -> DRepCredential -> Bool
PlutusTx.Eq
, DRepCredential -> BuiltinData
(DRepCredential -> BuiltinData) -> ToData DRepCredential
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: DRepCredential -> BuiltinData
toBuiltinData :: DRepCredential -> BuiltinData
PlutusTx.ToData
, BuiltinData -> Maybe DRepCredential
(BuiltinData -> Maybe DRepCredential) -> FromData DRepCredential
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe DRepCredential
fromBuiltinData :: BuiltinData -> Maybe DRepCredential
PlutusTx.FromData
, BuiltinData -> DRepCredential
(BuiltinData -> DRepCredential) -> UnsafeFromData DRepCredential
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> DRepCredential
unsafeFromBuiltinData :: BuiltinData -> DRepCredential
PlutusTx.UnsafeFromData
)
PlutusTx.makeLift ''DRepCredential
PlutusTx.asData
[d|
data DRep
= DRep DRepCredential
| DRepAlwaysAbstain
| DRepAlwaysNoConfidence
deriving stock (Generic, Haskell.Show, Haskell.Eq)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
deriving (Pretty) via (PrettyShow DRep)
|]
PlutusTx.makeLift ''DRep
instance PlutusTx.Eq DRep where
{-# INLINEABLE (==) #-}
DRep DRepCredential
a == :: DRep -> DRep -> Bool
== DRep DRepCredential
a' = DRepCredential
a DRepCredential -> DRepCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRepCredential
a'
DRep
DRepAlwaysAbstain == DRep
DRepAlwaysAbstain = Bool
Haskell.True
DRep
DRepAlwaysNoConfidence == DRep
DRepAlwaysNoConfidence = Bool
Haskell.True
DRep
_ == DRep
_ = Bool
Haskell.False
PlutusTx.asData
[d|
data Delegatee
= DelegStake V2.PubKeyHash
| DelegVote DRep
| DelegStakeVote V2.PubKeyHash DRep
deriving stock (Generic, Haskell.Show, Haskell.Eq)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
deriving (Pretty) via (PrettyShow Delegatee)
|]
PlutusTx.makeLift ''Delegatee
instance PlutusTx.Eq Delegatee where
{-# INLINEABLE (==) #-}
DelegStake PubKeyHash
a == :: Delegatee -> Delegatee -> Bool
== DelegStake PubKeyHash
a' = PubKeyHash
a PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== PubKeyHash
a'
DelegVote DRep
a == DelegVote DRep
a' = DRep
a DRep -> DRep -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRep
a'
DelegStakeVote PubKeyHash
a DRep
b == DelegStakeVote PubKeyHash
a' DRep
b' =
PubKeyHash
a PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== PubKeyHash
a' Bool -> Bool -> Bool
PlutusTx.&& DRep
b DRep -> DRep -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRep
b'
Delegatee
_ == Delegatee
_ = Bool
Haskell.False
PlutusTx.asData
[d|
data TxCert
=
TxCertRegStaking V2.Credential (Haskell.Maybe V2.Lovelace)
|
TxCertUnRegStaking V2.Credential (Haskell.Maybe V2.Lovelace)
|
TxCertDelegStaking V2.Credential Delegatee
|
TxCertRegDeleg V2.Credential Delegatee V2.Lovelace
|
TxCertRegDRep DRepCredential V2.Lovelace
|
TxCertUpdateDRep DRepCredential
|
TxCertUnRegDRep DRepCredential V2.Lovelace
|
TxCertPoolRegister
V2.PubKeyHash
V2.PubKeyHash
|
TxCertPoolRetire V2.PubKeyHash Haskell.Integer
|
TxCertAuthHotCommittee ColdCommitteeCredential HotCommitteeCredential
| TxCertResignColdCommittee ColdCommitteeCredential
deriving stock (Generic, Haskell.Show, Haskell.Eq)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
deriving (Pretty) via (PrettyShow TxCert)
|]
PlutusTx.makeLift ''TxCert
instance PlutusTx.Eq TxCert where
{-# INLINEABLE (==) #-}
TxCertRegStaking Credential
a Maybe Lovelace
b == :: TxCert -> TxCert -> Bool
== TxCertRegStaking Credential
a' Maybe Lovelace
b' =
Credential
a Credential -> Credential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Credential
a' Bool -> Bool -> Bool
PlutusTx.&& Maybe Lovelace
b Maybe Lovelace -> Maybe Lovelace -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Maybe Lovelace
b'
TxCertUnRegStaking Credential
a Maybe Lovelace
b == TxCertUnRegStaking Credential
a' Maybe Lovelace
b' =
Credential
a Credential -> Credential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Credential
a' Bool -> Bool -> Bool
PlutusTx.&& Maybe Lovelace
b Maybe Lovelace -> Maybe Lovelace -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Maybe Lovelace
b'
TxCertDelegStaking Credential
a Delegatee
b == TxCertDelegStaking Credential
a' Delegatee
b' =
Credential
a Credential -> Credential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Credential
a' Bool -> Bool -> Bool
PlutusTx.&& Delegatee
b Delegatee -> Delegatee -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Delegatee
b'
TxCertRegDeleg Credential
a Delegatee
b Lovelace
c == TxCertRegDeleg Credential
a' Delegatee
b' Lovelace
c' =
Credential
a Credential -> Credential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Credential
a' Bool -> Bool -> Bool
PlutusTx.&& Delegatee
b Delegatee -> Delegatee -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Delegatee
b' Bool -> Bool -> Bool
PlutusTx.&& Lovelace
c Lovelace -> Lovelace -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Lovelace
c'
TxCertRegDRep DRepCredential
a Lovelace
b == TxCertRegDRep DRepCredential
a' Lovelace
b' =
DRepCredential
a DRepCredential -> DRepCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRepCredential
a' Bool -> Bool -> Bool
PlutusTx.&& Lovelace
b Lovelace -> Lovelace -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Lovelace
b'
TxCertUpdateDRep DRepCredential
a == TxCertUpdateDRep DRepCredential
a' =
DRepCredential
a DRepCredential -> DRepCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRepCredential
a'
TxCertUnRegDRep DRepCredential
a Lovelace
b == TxCertUnRegDRep DRepCredential
a' Lovelace
b' =
DRepCredential
a DRepCredential -> DRepCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRepCredential
a' Bool -> Bool -> Bool
PlutusTx.&& Lovelace
b Lovelace -> Lovelace -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Lovelace
b'
TxCertAuthHotCommittee ColdCommitteeCredential
a HotCommitteeCredential
b == TxCertAuthHotCommittee ColdCommitteeCredential
a' HotCommitteeCredential
b' =
ColdCommitteeCredential
a ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== ColdCommitteeCredential
a' Bool -> Bool -> Bool
PlutusTx.&& HotCommitteeCredential
b HotCommitteeCredential -> HotCommitteeCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== HotCommitteeCredential
b'
TxCertResignColdCommittee ColdCommitteeCredential
a == TxCertResignColdCommittee ColdCommitteeCredential
a' =
ColdCommitteeCredential
a ColdCommitteeCredential -> ColdCommitteeCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== ColdCommitteeCredential
a'
TxCert
_ == TxCert
_ = Bool
Haskell.False
PlutusTx.asData
[d|
data Voter
= CommitteeVoter HotCommitteeCredential
| DRepVoter DRepCredential
| StakePoolVoter V2.PubKeyHash
deriving stock (Generic, Haskell.Show, Haskell.Eq)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
deriving (Pretty) via (PrettyShow Voter)
|]
PlutusTx.makeLift ''Voter
instance PlutusTx.Eq Voter where
{-# INLINEABLE (==) #-}
CommitteeVoter HotCommitteeCredential
a == :: Voter -> Voter -> Bool
== CommitteeVoter HotCommitteeCredential
a' =
HotCommitteeCredential
a HotCommitteeCredential -> HotCommitteeCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== HotCommitteeCredential
a'
DRepVoter DRepCredential
a == DRepVoter DRepCredential
a' =
DRepCredential
a DRepCredential -> DRepCredential -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== DRepCredential
a'
StakePoolVoter PubKeyHash
a == StakePoolVoter PubKeyHash
a' =
PubKeyHash
a PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== PubKeyHash
a'
Voter
_ == Voter
_ = Bool
Haskell.False
PlutusTx.asData
[d|
data Vote
= VoteNo
| VoteYes
| Abstain
deriving stock (Generic, Haskell.Show, Haskell.Eq)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
deriving (Pretty) via (PrettyShow Vote)
|]
PlutusTx.makeLift ''Vote
instance PlutusTx.Eq Vote where
{-# INLINEABLE (==) #-}
Vote
VoteNo == :: Vote -> Vote -> Bool
== Vote
VoteNo = Bool
Haskell.True
Vote
VoteYes == Vote
VoteYes = Bool
Haskell.True
Vote
Abstain == Vote
Abstain = Bool
Haskell.True
Vote
_ == Vote
_ = Bool
Haskell.False
PlutusTx.asData
[d|
data GovernanceActionId = GovernanceActionId
{ gaidTxId :: V3.TxId
, gaidGovActionIx :: Haskell.Integer
}
deriving stock (Generic, Haskell.Show, Haskell.Eq)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
|]
PlutusTx.makeLift ''GovernanceActionId
instance Pretty GovernanceActionId where
pretty :: forall ann. GovernanceActionId -> Doc ann
pretty GovernanceActionId{Integer
TxId
gaidTxId :: GovernanceActionId -> TxId
gaidGovActionIx :: GovernanceActionId -> Integer
gaidTxId :: TxId
gaidGovActionIx :: Integer
..} =
[Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
[ Doc ann
"gaidTxId:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxId -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. TxId -> Doc ann
pretty TxId
gaidTxId
, Doc ann
"gaidGovActionIx:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Integer -> Doc ann
forall ann. Integer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Integer
gaidGovActionIx
]
instance PlutusTx.Eq GovernanceActionId where
{-# INLINEABLE (==) #-}
GovernanceActionId TxId
a Integer
b == :: GovernanceActionId -> GovernanceActionId -> Bool
== GovernanceActionId TxId
a' Integer
b' =
TxId
a TxId -> TxId -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxId
a' Bool -> Bool -> Bool
PlutusTx.&& Integer
b Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Integer
b'
PlutusTx.asData
[d|
data Committee = Committee
{ committeeMembers :: Map ColdCommitteeCredential Haskell.Integer
,
committeeQuorum :: PlutusTx.Rational
}
deriving stock (Generic, Haskell.Show)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
|]
PlutusTx.makeLift ''Committee
instance Pretty Committee where
pretty :: forall ann. Committee -> Doc ann
pretty Committee{Rational
Map ColdCommitteeCredential Integer
committeeMembers :: Committee -> Map ColdCommitteeCredential Integer
committeeQuorum :: Committee -> Rational
committeeMembers :: Map ColdCommitteeCredential Integer
committeeQuorum :: Rational
..} =
[Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
[ Doc ann
"committeeMembers:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Map ColdCommitteeCredential Integer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Map ColdCommitteeCredential Integer -> Doc ann
pretty Map ColdCommitteeCredential Integer
committeeMembers
, Doc ann
"committeeQuorum:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Rational -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Rational -> Doc ann
pretty Rational
committeeQuorum
]
newtype Constitution = Constitution
{ Constitution -> Maybe ScriptHash
constitutionScript :: Haskell.Maybe V2.ScriptHash
}
deriving stock ((forall x. Constitution -> Rep Constitution x)
-> (forall x. Rep Constitution x -> Constitution)
-> Generic Constitution
forall x. Rep Constitution x -> Constitution
forall x. Constitution -> Rep Constitution x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. Constitution -> Rep Constitution x
from :: forall x. Constitution -> Rep Constitution x
$cto :: forall x. Rep Constitution x -> Constitution
to :: forall x. Rep Constitution x -> Constitution
Generic)
deriving newtype (Int -> Constitution -> ShowS
[Constitution] -> ShowS
Constitution -> String
(Int -> Constitution -> ShowS)
-> (Constitution -> String)
-> ([Constitution] -> ShowS)
-> Show Constitution
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Constitution -> ShowS
showsPrec :: Int -> Constitution -> ShowS
$cshow :: Constitution -> String
show :: Constitution -> String
$cshowList :: [Constitution] -> ShowS
showList :: [Constitution] -> ShowS
Haskell.Show, Constitution -> Constitution -> Bool
(Constitution -> Constitution -> Bool)
-> (Constitution -> Constitution -> Bool) -> Eq Constitution
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Constitution -> Constitution -> Bool
== :: Constitution -> Constitution -> Bool
$c/= :: Constitution -> Constitution -> Bool
/= :: Constitution -> Constitution -> Bool
Haskell.Eq)
PlutusTx.makeLift ''Constitution
PlutusTx.makeIsDataIndexed ''Constitution [('Constitution, 0)]
instance Pretty Constitution where
pretty :: forall ann. Constitution -> Doc ann
pretty (Constitution Maybe ScriptHash
script) = Doc ann
"constitutionScript:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Maybe ScriptHash -> Doc ann
forall ann. Maybe ScriptHash -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Maybe ScriptHash
script
instance PlutusTx.Eq Constitution where
{-# INLINEABLE (==) #-}
Constitution Maybe ScriptHash
a == :: Constitution -> Constitution -> Bool
== Constitution Maybe ScriptHash
a' = Maybe ScriptHash
a Maybe ScriptHash -> Maybe ScriptHash -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Maybe ScriptHash
a'
PlutusTx.asData
[d|
data ProtocolVersion = ProtocolVersion
{ pvMajor :: Haskell.Integer
, pvMinor :: Haskell.Integer
}
deriving stock (Generic, Haskell.Show, Haskell.Eq)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
|]
PlutusTx.makeLift ''ProtocolVersion
instance Pretty ProtocolVersion where
pretty :: forall ann. ProtocolVersion -> Doc ann
pretty ProtocolVersion{Integer
pvMajor :: ProtocolVersion -> Integer
pvMinor :: ProtocolVersion -> Integer
pvMajor :: Integer
pvMinor :: Integer
..} =
[Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
[ Doc ann
"pvMajor:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Integer -> Doc ann
forall ann. Integer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Integer
pvMajor
, Doc ann
"pvMinor:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Integer -> Doc ann
forall ann. Integer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Integer
pvMinor
]
instance PlutusTx.Eq ProtocolVersion where
{-# INLINEABLE (==) #-}
ProtocolVersion Integer
a Integer
b == :: ProtocolVersion -> ProtocolVersion -> Bool
== ProtocolVersion Integer
a' Integer
b' =
Integer
a Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Integer
a' Bool -> Bool -> Bool
PlutusTx.&& Integer
b Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Integer
b'
newtype ChangedParameters = ChangedParameters {ChangedParameters -> BuiltinData
getChangedParameters :: PlutusTx.BuiltinData}
deriving stock ((forall x. ChangedParameters -> Rep ChangedParameters x)
-> (forall x. Rep ChangedParameters x -> ChangedParameters)
-> Generic ChangedParameters
forall x. Rep ChangedParameters x -> ChangedParameters
forall x. ChangedParameters -> Rep ChangedParameters x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ChangedParameters -> Rep ChangedParameters x
from :: forall x. ChangedParameters -> Rep ChangedParameters x
$cto :: forall x. Rep ChangedParameters x -> ChangedParameters
to :: forall x. Rep ChangedParameters x -> ChangedParameters
Generic, Int -> ChangedParameters -> ShowS
[ChangedParameters] -> ShowS
ChangedParameters -> String
(Int -> ChangedParameters -> ShowS)
-> (ChangedParameters -> String)
-> ([ChangedParameters] -> ShowS)
-> Show ChangedParameters
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ChangedParameters -> ShowS
showsPrec :: Int -> ChangedParameters -> ShowS
$cshow :: ChangedParameters -> String
show :: ChangedParameters -> String
$cshowList :: [ChangedParameters] -> ShowS
showList :: [ChangedParameters] -> ShowS
Haskell.Show)
deriving newtype
( ChangedParameters -> ChangedParameters -> Bool
(ChangedParameters -> ChangedParameters -> Bool)
-> (ChangedParameters -> ChangedParameters -> Bool)
-> Eq ChangedParameters
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ChangedParameters -> ChangedParameters -> Bool
== :: ChangedParameters -> ChangedParameters -> Bool
$c/= :: ChangedParameters -> ChangedParameters -> Bool
/= :: ChangedParameters -> ChangedParameters -> Bool
Haskell.Eq
, Eq ChangedParameters
Eq ChangedParameters =>
(ChangedParameters -> ChangedParameters -> Ordering)
-> (ChangedParameters -> ChangedParameters -> Bool)
-> (ChangedParameters -> ChangedParameters -> Bool)
-> (ChangedParameters -> ChangedParameters -> Bool)
-> (ChangedParameters -> ChangedParameters -> Bool)
-> (ChangedParameters -> ChangedParameters -> ChangedParameters)
-> (ChangedParameters -> ChangedParameters -> ChangedParameters)
-> Ord ChangedParameters
ChangedParameters -> ChangedParameters -> Bool
ChangedParameters -> ChangedParameters -> Ordering
ChangedParameters -> ChangedParameters -> ChangedParameters
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 :: ChangedParameters -> ChangedParameters -> Ordering
compare :: ChangedParameters -> ChangedParameters -> Ordering
$c< :: ChangedParameters -> ChangedParameters -> Bool
< :: ChangedParameters -> ChangedParameters -> Bool
$c<= :: ChangedParameters -> ChangedParameters -> Bool
<= :: ChangedParameters -> ChangedParameters -> Bool
$c> :: ChangedParameters -> ChangedParameters -> Bool
> :: ChangedParameters -> ChangedParameters -> Bool
$c>= :: ChangedParameters -> ChangedParameters -> Bool
>= :: ChangedParameters -> ChangedParameters -> Bool
$cmax :: ChangedParameters -> ChangedParameters -> ChangedParameters
max :: ChangedParameters -> ChangedParameters -> ChangedParameters
$cmin :: ChangedParameters -> ChangedParameters -> ChangedParameters
min :: ChangedParameters -> ChangedParameters -> ChangedParameters
Haskell.Ord
, ChangedParameters -> ChangedParameters -> Bool
(ChangedParameters -> ChangedParameters -> Bool)
-> Eq ChangedParameters
forall a. (a -> a -> Bool) -> Eq a
$c== :: ChangedParameters -> ChangedParameters -> Bool
== :: ChangedParameters -> ChangedParameters -> Bool
PlutusTx.Eq
, ChangedParameters -> BuiltinData
(ChangedParameters -> BuiltinData) -> ToData ChangedParameters
forall a. (a -> BuiltinData) -> ToData a
$ctoBuiltinData :: ChangedParameters -> BuiltinData
toBuiltinData :: ChangedParameters -> BuiltinData
PlutusTx.ToData
, BuiltinData -> Maybe ChangedParameters
(BuiltinData -> Maybe ChangedParameters)
-> FromData ChangedParameters
forall a. (BuiltinData -> Maybe a) -> FromData a
$cfromBuiltinData :: BuiltinData -> Maybe ChangedParameters
fromBuiltinData :: BuiltinData -> Maybe ChangedParameters
PlutusTx.FromData
, BuiltinData -> ChangedParameters
(BuiltinData -> ChangedParameters)
-> UnsafeFromData ChangedParameters
forall a. (BuiltinData -> a) -> UnsafeFromData a
$cunsafeFromBuiltinData :: BuiltinData -> ChangedParameters
unsafeFromBuiltinData :: BuiltinData -> ChangedParameters
PlutusTx.UnsafeFromData
, (forall ann. ChangedParameters -> Doc ann)
-> (forall ann. [ChangedParameters] -> Doc ann)
-> Pretty ChangedParameters
forall ann. [ChangedParameters] -> Doc ann
forall ann. ChangedParameters -> Doc ann
forall a.
(forall ann. a -> Doc ann)
-> (forall ann. [a] -> Doc ann) -> Pretty a
$cpretty :: forall ann. ChangedParameters -> Doc ann
pretty :: forall ann. ChangedParameters -> Doc ann
$cprettyList :: forall ann. [ChangedParameters] -> Doc ann
prettyList :: forall ann. [ChangedParameters] -> Doc ann
Pretty
)
PlutusTx.makeLift ''ChangedParameters
PlutusTx.asData
[d|
data GovernanceAction
= ParameterChange
(Haskell.Maybe GovernanceActionId)
ChangedParameters
(Haskell.Maybe V2.ScriptHash)
|
HardForkInitiation (Haskell.Maybe GovernanceActionId) ProtocolVersion
| TreasuryWithdrawals
(Map V2.Credential V2.Lovelace)
(Haskell.Maybe V2.ScriptHash)
|
NoConfidence (Haskell.Maybe GovernanceActionId)
| UpdateCommittee
(Haskell.Maybe GovernanceActionId)
(List ColdCommitteeCredential)
(Map ColdCommitteeCredential Haskell.Integer)
Rational
|
NewConstitution (Haskell.Maybe GovernanceActionId) Constitution
| InfoAction
deriving stock (Generic, Haskell.Show)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
deriving (Pretty) via (PrettyShow GovernanceAction)
|]
PlutusTx.makeLift ''GovernanceAction
PlutusTx.asData
[d|
data ProposalProcedure = ProposalProcedure
{ ppDeposit :: V2.Lovelace
, ppReturnAddr :: V2.Credential
, ppGovernanceAction :: GovernanceAction
}
deriving stock (Generic, Haskell.Show)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
|]
PlutusTx.makeLift ''ProposalProcedure
instance Pretty ProposalProcedure where
pretty :: forall ann. ProposalProcedure -> Doc ann
pretty ProposalProcedure{Credential
GovernanceAction
Lovelace
ppDeposit :: ProposalProcedure -> Lovelace
ppReturnAddr :: ProposalProcedure -> Credential
ppGovernanceAction :: ProposalProcedure -> GovernanceAction
ppDeposit :: Lovelace
ppReturnAddr :: Credential
ppGovernanceAction :: GovernanceAction
..} =
[Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
[ Doc ann
"ppDeposit:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Lovelace -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Lovelace -> Doc ann
pretty Lovelace
ppDeposit
, Doc ann
"ppReturnAddr:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Credential -> Doc ann
forall ann. Credential -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Credential
ppReturnAddr
, Doc ann
"ppGovernanceAction:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> GovernanceAction -> Doc ann
forall ann. GovernanceAction -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty GovernanceAction
ppGovernanceAction
]
PlutusTx.asData
[d|
data ScriptPurpose
= Minting V2.CurrencySymbol
| Spending V3.TxOutRef
| Rewarding V2.Credential
| Certifying
Haskell.Integer
TxCert
| Voting Voter
| Proposing
Haskell.Integer
ProposalProcedure
deriving stock (Generic, Haskell.Show)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
deriving (Pretty) via (PrettyShow ScriptPurpose)
|]
PlutusTx.makeLift ''ScriptPurpose
PlutusTx.asData
[d|
data ScriptInfo
= MintingScript V2.CurrencySymbol
| SpendingScript V3.TxOutRef (Haskell.Maybe V2.Datum)
| RewardingScript V2.Credential
| CertifyingScript
Haskell.Integer
TxCert
| VotingScript Voter
| ProposingScript
Haskell.Integer
ProposalProcedure
deriving stock (Generic, Haskell.Show)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
deriving (Pretty) via (PrettyShow ScriptInfo)
|]
PlutusTx.makeLift ''ScriptInfo
PlutusTx.asData
[d|
data TxInInfo = TxInInfo
{ txInInfoOutRef :: V3.TxOutRef
, txInInfoResolved :: V2.TxOut
}
deriving stock (Generic, Haskell.Show, Haskell.Eq)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
|]
PlutusTx.makeLift ''TxInInfo
instance PlutusTx.Eq TxInInfo where
TxInInfo TxOutRef
ref TxOut
res == :: TxInInfo -> TxInInfo -> Bool
== TxInInfo TxOutRef
ref' TxOut
res' =
TxOutRef
ref TxOutRef -> TxOutRef -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxOutRef
ref' Bool -> Bool -> Bool
PlutusTx.&& TxOut
res TxOut -> TxOut -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxOut
res'
instance Pretty TxInInfo where
pretty :: forall ann. TxInInfo -> Doc ann
pretty TxInInfo{TxOutRef
txInInfoOutRef :: TxInInfo -> TxOutRef
txInInfoOutRef :: TxOutRef
txInInfoOutRef, TxOut
txInInfoResolved :: TxInInfo -> TxOut
txInInfoResolved :: TxOut
txInInfoResolved} =
TxOutRef -> Doc ann
forall ann. TxOutRef -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOutRef
txInInfoOutRef Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
"->" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxOut -> Doc ann
forall ann. TxOut -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxOut
txInInfoResolved
PlutusTx.asData
[d|
data TxInfo = TxInfo
{ txInfoInputs :: List TxInInfo
, txInfoReferenceInputs :: List TxInInfo
, txInfoOutputs :: List V2.TxOut
, txInfoFee :: V2.Lovelace
, txInfoMint :: V2.Value
,
txInfoTxCerts :: List TxCert
, txInfoWdrl :: Map V2.Credential V2.Lovelace
, txInfoValidRange :: V2.POSIXTimeRange
, txInfoSignatories :: List V2.PubKeyHash
, txInfoRedeemers :: Map ScriptPurpose V2.Redeemer
, txInfoData :: Map V2.DatumHash V2.Datum
, txInfoId :: V3.TxId
, txInfoVotes :: Map Voter (Map GovernanceActionId Vote)
, txInfoProposalProcedures :: List ProposalProcedure
, txInfoCurrentTreasuryAmount :: Haskell.Maybe V2.Lovelace
, txInfoTreasuryDonation :: Haskell.Maybe V2.Lovelace
}
deriving stock (Generic, Haskell.Show)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
|]
PlutusTx.makeLift ''TxInfo
PlutusTx.asData
[d|
data ScriptContext = ScriptContext
{ scriptContextTxInfo :: TxInfo
,
scriptContextRedeemer :: V2.Redeemer
,
scriptContextScriptInfo :: ScriptInfo
}
deriving stock (Generic, Haskell.Show)
deriving newtype (PlutusTx.FromData, PlutusTx.UnsafeFromData, PlutusTx.ToData)
|]
PlutusTx.makeLift ''ScriptContext
{-# INLINEABLE findOwnInput #-}
findOwnInput :: ScriptContext -> Haskell.Maybe TxInInfo
findOwnInput :: ScriptContext -> Maybe TxInInfo
findOwnInput
ScriptContext
{ scriptContextTxInfo :: ScriptContext -> TxInfo
scriptContextTxInfo = TxInfo{List TxInInfo
txInfoInputs :: TxInfo -> List TxInInfo
txInfoInputs :: List TxInInfo
txInfoInputs}
, scriptContextScriptInfo :: ScriptContext -> ScriptInfo
scriptContextScriptInfo = SpendingScript TxOutRef
txOutRef Maybe Datum
_
} =
(TxInInfo -> Bool) -> List TxInInfo -> Maybe TxInInfo
forall a. UnsafeFromData a => (a -> Bool) -> List a -> Maybe a
Data.List.find
(\TxInInfo{TxOutRef
txInInfoOutRef :: TxInInfo -> TxOutRef
txInInfoOutRef :: TxOutRef
txInInfoOutRef} -> TxOutRef
txInInfoOutRef TxOutRef -> TxOutRef -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxOutRef
txOutRef)
List TxInInfo
txInfoInputs
findOwnInput ScriptContext
_ = Maybe TxInInfo
forall a. Maybe a
Haskell.Nothing
{-# INLINEABLE findDatum #-}
findDatum :: V2.DatumHash -> TxInfo -> Haskell.Maybe V2.Datum
findDatum :: DatumHash -> TxInfo -> Maybe Datum
findDatum DatumHash
dsh TxInfo{Map DatumHash Datum
txInfoData :: TxInfo -> Map DatumHash Datum
txInfoData :: Map DatumHash Datum
txInfoData} = DatumHash -> Map DatumHash Datum -> Maybe Datum
forall k a. (ToData k, UnsafeFromData a) => k -> Map k a -> Maybe a
lookup DatumHash
dsh Map DatumHash Datum
txInfoData
{-# INLINEABLE findDatumHash #-}
findDatumHash :: V2.Datum -> TxInfo -> Haskell.Maybe V2.DatumHash
findDatumHash :: Datum -> TxInfo -> Maybe DatumHash
findDatumHash Datum
ds TxInfo{Map DatumHash Datum
txInfoData :: TxInfo -> Map DatumHash Datum
txInfoData :: Map DatumHash Datum
txInfoData} =
(DatumHash, Datum) -> DatumHash
forall a b. (a, b) -> a
PlutusTx.fst ((DatumHash, Datum) -> DatumHash)
-> Maybe (DatumHash, Datum) -> Maybe DatumHash
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
PlutusTx.<$> ((DatumHash, Datum) -> Bool)
-> [(DatumHash, Datum)] -> Maybe (DatumHash, Datum)
forall a. (a -> Bool) -> [a] -> Maybe a
PlutusTx.find (DatumHash, Datum) -> Bool
forall {a}. (a, Datum) -> Bool
f (Map DatumHash Datum -> [(DatumHash, Datum)]
forall k a.
(UnsafeFromData k, UnsafeFromData a) =>
Map k a -> [(k, a)]
toList Map DatumHash Datum
txInfoData)
where
f :: (a, Datum) -> Bool
f (a
_, Datum
ds') = Datum
ds' Datum -> Datum -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Datum
ds
{-# INLINEABLE findTxInByTxOutRef #-}
findTxInByTxOutRef :: V3.TxOutRef -> TxInfo -> Haskell.Maybe TxInInfo
findTxInByTxOutRef :: TxOutRef -> TxInfo -> Maybe TxInInfo
findTxInByTxOutRef TxOutRef
outRef TxInfo{List TxInInfo
txInfoInputs :: TxInfo -> List TxInInfo
txInfoInputs :: List TxInInfo
txInfoInputs} =
(TxInInfo -> Bool) -> List TxInInfo -> Maybe TxInInfo
forall a. UnsafeFromData a => (a -> Bool) -> List a -> Maybe a
Data.List.find
(\TxInInfo{TxOutRef
txInInfoOutRef :: TxInInfo -> TxOutRef
txInInfoOutRef :: TxOutRef
txInInfoOutRef} -> TxOutRef
txInInfoOutRef TxOutRef -> TxOutRef -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxOutRef
outRef)
List TxInInfo
txInfoInputs
{-# INLINEABLE findContinuingOutputs #-}
findContinuingOutputs :: ScriptContext -> List Haskell.Integer
findContinuingOutputs :: ScriptContext -> List Integer
findContinuingOutputs ScriptContext
ctx
| Haskell.Just TxInInfo{txInInfoResolved :: TxInInfo -> TxOut
txInInfoResolved = V2.TxOut{Address
txOutAddress :: TxOut -> Address
txOutAddress :: Address
txOutAddress}} <-
ScriptContext -> Maybe TxInInfo
findOwnInput ScriptContext
ctx =
(TxOut -> Bool) -> List TxOut -> List Integer
forall a. UnsafeFromData a => (a -> Bool) -> List a -> List Integer
Data.List.findIndices
(Address -> TxOut -> Bool
f Address
txOutAddress)
(TxInfo -> List TxOut
txInfoOutputs (ScriptContext -> TxInfo
scriptContextTxInfo ScriptContext
ctx))
where
f :: Address -> TxOut -> Bool
f Address
addr V2.TxOut{txOutAddress :: TxOut -> Address
txOutAddress = Address
otherAddress} = Address
addr Address -> Address -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Address
otherAddress
findContinuingOutputs ScriptContext
_ = BuiltinString -> List Integer
forall a. BuiltinString -> a
PlutusTx.traceError BuiltinString
"Le"
{-# INLINEABLE getContinuingOutputs #-}
getContinuingOutputs :: ScriptContext -> List V2.TxOut
getContinuingOutputs :: ScriptContext -> List TxOut
getContinuingOutputs ScriptContext
ctx
| Haskell.Just TxInInfo{txInInfoResolved :: TxInInfo -> TxOut
txInInfoResolved = V2.TxOut{Address
txOutAddress :: TxOut -> Address
txOutAddress :: Address
txOutAddress}} <-
ScriptContext -> Maybe TxInInfo
findOwnInput ScriptContext
ctx =
(TxOut -> Bool) -> List TxOut -> List TxOut
forall a.
(UnsafeFromData a, ToData a) =>
(a -> Bool) -> List a -> List a
Data.List.filter (Address -> TxOut -> Bool
f Address
txOutAddress) (TxInfo -> List TxOut
txInfoOutputs (ScriptContext -> TxInfo
scriptContextTxInfo ScriptContext
ctx))
where
f :: Address -> TxOut -> Bool
f Address
addr V2.TxOut{txOutAddress :: TxOut -> Address
txOutAddress = Address
otherAddress} = Address
addr Address -> Address -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== Address
otherAddress
getContinuingOutputs ScriptContext
_ = BuiltinString -> List TxOut
forall a. BuiltinString -> a
PlutusTx.traceError BuiltinString
"Lf"
{-# INLINEABLE txSignedBy #-}
txSignedBy :: TxInfo -> V2.PubKeyHash -> Haskell.Bool
txSignedBy :: TxInfo -> PubKeyHash -> Bool
txSignedBy TxInfo{List PubKeyHash
txInfoSignatories :: TxInfo -> List PubKeyHash
txInfoSignatories :: List PubKeyHash
txInfoSignatories} PubKeyHash
k = case (PubKeyHash -> Bool) -> List PubKeyHash -> Maybe PubKeyHash
forall a. UnsafeFromData a => (a -> Bool) -> List a -> Maybe a
Data.List.find (PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
(PlutusTx.==) PubKeyHash
k) List PubKeyHash
txInfoSignatories of
Haskell.Just PubKeyHash
_ -> Bool
Haskell.True
Maybe PubKeyHash
Haskell.Nothing -> Bool
Haskell.False
{-# INLINEABLE pubKeyOutputsAt #-}
pubKeyOutputsAt :: V2.PubKeyHash -> TxInfo -> List V2.Value
pubKeyOutputsAt :: PubKeyHash -> TxInfo -> List Value
pubKeyOutputsAt PubKeyHash
pk TxInfo
p =
let flt :: TxOut -> Maybe Value
flt V2.TxOut{txOutAddress :: TxOut -> Address
txOutAddress = V2.Address (V2.PubKeyCredential PubKeyHash
pk') Maybe StakingCredential
_, Value
txOutValue :: TxOut -> Value
txOutValue :: Value
txOutValue}
| PubKeyHash
pk PubKeyHash -> PubKeyHash -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== PubKeyHash
pk' = Value -> Maybe Value
forall a. a -> Maybe a
Haskell.Just Value
txOutValue
flt TxOut
_ = Maybe Value
forall a. Maybe a
Haskell.Nothing
in (TxOut -> Maybe Value) -> List TxOut -> List Value
forall a b.
(UnsafeFromData a, ToData b) =>
(a -> Maybe b) -> List a -> List b
Data.List.mapMaybe TxOut -> Maybe Value
flt (TxInfo -> List TxOut
txInfoOutputs TxInfo
p)
{-# INLINEABLE valuePaidTo #-}
valuePaidTo :: TxInfo -> V2.PubKeyHash -> V2.Value
valuePaidTo :: TxInfo -> PubKeyHash -> Value
valuePaidTo TxInfo
ptx PubKeyHash
pkh = List Value -> Value
forall a. (Monoid a, UnsafeFromData a) => List a -> a
Data.List.mconcat (PubKeyHash -> TxInfo -> List Value
pubKeyOutputsAt PubKeyHash
pkh TxInfo
ptx)
{-# INLINEABLE valueSpent #-}
valueSpent :: TxInfo -> V2.Value
valueSpent :: TxInfo -> Value
valueSpent =
(TxInInfo -> Value) -> List TxInInfo -> Value
forall a m. (UnsafeFromData a, Monoid m) => (a -> m) -> List a -> m
Data.List.foldMap (TxOut -> Value
V2.txOutValue (TxOut -> Value) -> (TxInInfo -> TxOut) -> TxInInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
PlutusTx.. TxInInfo -> TxOut
txInInfoResolved) (List TxInInfo -> Value)
-> (TxInfo -> List TxInInfo) -> TxInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
PlutusTx.. TxInfo -> List TxInInfo
txInfoInputs
{-# INLINEABLE valueProduced #-}
valueProduced :: TxInfo -> V2.Value
valueProduced :: TxInfo -> Value
valueProduced = (TxOut -> Value) -> List TxOut -> Value
forall a m. (UnsafeFromData a, Monoid m) => (a -> m) -> List a -> m
Data.List.foldMap TxOut -> Value
V2.txOutValue (List TxOut -> Value) -> (TxInfo -> List TxOut) -> TxInfo -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
PlutusTx.. TxInfo -> List TxOut
txInfoOutputs
{-# INLINEABLE ownCurrencySymbol #-}
ownCurrencySymbol :: ScriptContext -> V2.CurrencySymbol
ownCurrencySymbol :: ScriptContext -> CurrencySymbol
ownCurrencySymbol ScriptContext{scriptContextScriptInfo :: ScriptContext -> ScriptInfo
scriptContextScriptInfo = MintingScript CurrencySymbol
cs} = CurrencySymbol
cs
ownCurrencySymbol ScriptContext
_ =
BuiltinString -> CurrencySymbol
forall a. BuiltinString -> a
PlutusTx.traceError BuiltinString
"Lh"
{-# INLINEABLE spendsOutput #-}
spendsOutput :: TxInfo -> V3.TxId -> Haskell.Integer -> Haskell.Bool
spendsOutput :: TxInfo -> TxId -> Integer -> Bool
spendsOutput TxInfo
txInfo TxId
txId Integer
i =
let spendsOutRef :: TxInInfo -> Bool
spendsOutRef TxInInfo
inp =
let outRef :: TxOutRef
outRef = TxInInfo -> TxOutRef
txInInfoOutRef TxInInfo
inp
in TxId
txId
TxId -> TxId -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxOutRef -> TxId
V3.txOutRefId TxOutRef
outRef
Bool -> Bool -> Bool
PlutusTx.&& Integer
i
Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
PlutusTx.== TxOutRef -> Integer
V3.txOutRefIdx TxOutRef
outRef
in (TxInInfo -> Bool) -> List TxInInfo -> Bool
forall a. UnsafeFromData a => (a -> Bool) -> List a -> Bool
Data.List.any TxInInfo -> Bool
spendsOutRef (TxInfo -> List TxInInfo
txInfoInputs TxInfo
txInfo)
instance Pretty TxInfo where
pretty :: forall ann. TxInfo -> Doc ann
pretty TxInfo{Maybe Lovelace
POSIXTimeRange
List TxOut
List TxCert
List ProposalProcedure
List TxInInfo
List PubKeyHash
Map Credential Lovelace
Map Voter (Map GovernanceActionId Vote)
Map ScriptPurpose Redeemer
Map DatumHash Datum
TxId
Lovelace
Value
txInfoInputs :: TxInfo -> List TxInInfo
txInfoReferenceInputs :: TxInfo -> List TxInInfo
txInfoOutputs :: TxInfo -> List TxOut
txInfoFee :: TxInfo -> Lovelace
txInfoMint :: TxInfo -> Value
txInfoTxCerts :: TxInfo -> List TxCert
txInfoWdrl :: TxInfo -> Map Credential Lovelace
txInfoValidRange :: TxInfo -> POSIXTimeRange
txInfoSignatories :: TxInfo -> List PubKeyHash
txInfoRedeemers :: TxInfo -> Map ScriptPurpose Redeemer
txInfoData :: TxInfo -> Map DatumHash Datum
txInfoId :: TxInfo -> TxId
txInfoVotes :: TxInfo -> Map Voter (Map GovernanceActionId Vote)
txInfoProposalProcedures :: TxInfo -> List ProposalProcedure
txInfoCurrentTreasuryAmount :: TxInfo -> Maybe Lovelace
txInfoTreasuryDonation :: TxInfo -> Maybe Lovelace
txInfoInputs :: List TxInInfo
txInfoReferenceInputs :: List TxInInfo
txInfoOutputs :: List TxOut
txInfoFee :: Lovelace
txInfoMint :: Value
txInfoTxCerts :: List TxCert
txInfoWdrl :: Map Credential Lovelace
txInfoValidRange :: POSIXTimeRange
txInfoSignatories :: List PubKeyHash
txInfoRedeemers :: Map ScriptPurpose Redeemer
txInfoData :: Map DatumHash Datum
txInfoId :: TxId
txInfoVotes :: Map Voter (Map GovernanceActionId Vote)
txInfoProposalProcedures :: List ProposalProcedure
txInfoCurrentTreasuryAmount :: Maybe Lovelace
txInfoTreasuryDonation :: Maybe Lovelace
..} =
[Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
[ Doc ann
"TxId:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> TxId -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. TxId -> Doc ann
pretty TxId
txInfoId
, Doc ann
"Inputs:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> List TxInInfo -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. List TxInInfo -> Doc ann
pretty List TxInInfo
txInfoInputs
, Doc ann
"Reference inputs:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> List TxInInfo -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. List TxInInfo -> Doc ann
pretty List TxInInfo
txInfoReferenceInputs
, Doc ann
"Outputs:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> List TxOut -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. List TxOut -> Doc ann
pretty List TxOut
txInfoOutputs
, Doc ann
"Fee:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Lovelace -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Lovelace -> Doc ann
pretty Lovelace
txInfoFee
, Doc ann
"Value minted:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Value -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Value -> Doc ann
pretty Value
txInfoMint
, Doc ann
"TxCerts:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> List TxCert -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. List TxCert -> Doc ann
pretty List TxCert
txInfoTxCerts
, Doc ann
"Wdrl:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Map Credential Lovelace -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Map Credential Lovelace -> Doc ann
pretty Map Credential Lovelace
txInfoWdrl
, Doc ann
"Valid range:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> POSIXTimeRange -> Doc ann
forall ann. POSIXTimeRange -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty POSIXTimeRange
txInfoValidRange
, Doc ann
"Signatories:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> List PubKeyHash -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. List PubKeyHash -> Doc ann
pretty List PubKeyHash
txInfoSignatories
, Doc ann
"Redeemers:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Map ScriptPurpose Redeemer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Map ScriptPurpose Redeemer -> Doc ann
pretty Map ScriptPurpose Redeemer
txInfoRedeemers
, Doc ann
"Datums:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Map DatumHash Datum -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Map DatumHash Datum -> Doc ann
pretty Map DatumHash Datum
txInfoData
, Doc ann
"Votes:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Map Voter (Map GovernanceActionId Vote) -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Map Voter (Map GovernanceActionId Vote) -> Doc ann
pretty Map Voter (Map GovernanceActionId Vote)
txInfoVotes
, Doc ann
"Proposal Procedures:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> List ProposalProcedure -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. List ProposalProcedure -> Doc ann
pretty List ProposalProcedure
txInfoProposalProcedures
, Doc ann
"Current Treasury Amount:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Maybe Lovelace -> Doc ann
forall ann. Maybe Lovelace -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Maybe Lovelace
txInfoCurrentTreasuryAmount
, Doc ann
"Treasury Donation:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> Maybe Lovelace -> Doc ann
forall ann. Maybe Lovelace -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty Maybe Lovelace
txInfoTreasuryDonation
]
instance Pretty ScriptContext where
pretty :: forall ann. ScriptContext -> Doc ann
pretty ScriptContext{ScriptInfo
TxInfo
Redeemer
scriptContextTxInfo :: ScriptContext -> TxInfo
scriptContextRedeemer :: ScriptContext -> Redeemer
scriptContextScriptInfo :: ScriptContext -> ScriptInfo
scriptContextTxInfo :: TxInfo
scriptContextRedeemer :: Redeemer
scriptContextScriptInfo :: ScriptInfo
..} =
[Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep
[ Doc ann
"ScriptInfo:" Doc ann -> Doc ann -> Doc ann
forall ann. Doc ann -> Doc ann -> Doc ann
<+> ScriptInfo -> Doc ann
forall ann. ScriptInfo -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty ScriptInfo
scriptContextScriptInfo
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
nest Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"TxInfo:", TxInfo -> Doc ann
forall ann. TxInfo -> Doc ann
forall a ann. Pretty a => a -> Doc ann
pretty TxInfo
scriptContextTxInfo])
, Int -> Doc ann -> Doc ann
forall ann. Int -> Doc ann -> Doc ann
nest Int
2 ([Doc ann] -> Doc ann
forall ann. [Doc ann] -> Doc ann
vsep [Doc ann
"Redeemer:", Redeemer -> Doc ann
forall a ann. Pretty a => a -> Doc ann
forall ann. Redeemer -> Doc ann
pretty Redeemer
scriptContextRedeemer])
]