{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingVia #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE QuantifiedConstraints #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE UndecidableSuperClasses #-} {-# LANGUAGE ViewPatterns #-} {-# OPTIONS_GHC -Wno-orphans #-} module Cardano.Ledger.Conway.Scripts ( ConwayEraScript (..), AlonzoScript (..), PlutusScript (..), isPlutusScript, ConwayPlutusPurpose (..), pattern VotingPurpose, pattern ProposingPurpose, ) where import Cardano.Ledger.Address (RewardAccount) import Cardano.Ledger.Allegra.Scripts import Cardano.Ledger.Alonzo.Scripts ( AlonzoPlutusPurpose (..), AlonzoScript (..), alonzoScriptPrefixTag, isPlutusScript, ) import Cardano.Ledger.Babbage.Core import Cardano.Ledger.Babbage.Scripts (PlutusScript (..)) import Cardano.Ledger.BaseTypes (kindObject) import Cardano.Ledger.Binary ( CBORGroup (..), DecCBOR (decCBOR), DecCBORGroup (..), EncCBOR (..), EncCBORGroup (..), decodeWord8, encodeWord8, ) import Cardano.Ledger.Conway.Era import Cardano.Ledger.Conway.Governance.Procedures import Cardano.Ledger.Conway.TxCert () import Cardano.Ledger.Mary.Value (PolicyID) import Cardano.Ledger.Plutus.Language import Cardano.Ledger.Shelley.Scripts (ShelleyEraScript (..)) import Cardano.Ledger.TxIn (TxIn) import Control.DeepSeq (NFData (..), rwhnf) import Data.Aeson (ToJSON (..), (.=)) import Data.MemPack import Data.Typeable import Data.Word (Word16, Word32, Word8) import GHC.Generics import NoThunks.Class (NoThunks (..)) class AlonzoEraScript era => ConwayEraScript era where mkVotingPurpose :: f Word32 Voter -> PlutusPurpose f era toVotingPurpose :: PlutusPurpose f era -> Maybe (f Word32 Voter) mkProposingPurpose :: f Word32 (ProposalProcedure era) -> PlutusPurpose f era toProposingPurpose :: PlutusPurpose f era -> Maybe (f Word32 (ProposalProcedure era)) instance EraScript ConwayEra where type Script ConwayEra = AlonzoScript ConwayEra type NativeScript ConwayEra = Timelock ConwayEra upgradeScript :: EraScript (PreviousEra ConwayEra) => Script (PreviousEra ConwayEra) -> Script ConwayEra upgradeScript = \case TimelockScript Timelock BabbageEra ts -> Timelock ConwayEra -> AlonzoScript ConwayEra forall era. Timelock era -> AlonzoScript era TimelockScript (Timelock ConwayEra -> AlonzoScript ConwayEra) -> Timelock ConwayEra -> AlonzoScript ConwayEra forall a b. (a -> b) -> a -> b $ Timelock BabbageEra -> Timelock ConwayEra forall era1 era2. (Era era1, Era era2) => Timelock era1 -> Timelock era2 translateTimelock Timelock BabbageEra ts PlutusScript (BabbagePlutusV1 Plutus 'PlutusV1 ps) -> PlutusScript ConwayEra -> AlonzoScript ConwayEra forall era. PlutusScript era -> AlonzoScript era PlutusScript (PlutusScript ConwayEra -> AlonzoScript ConwayEra) -> PlutusScript ConwayEra -> AlonzoScript ConwayEra forall a b. (a -> b) -> a -> b $ Plutus 'PlutusV1 -> PlutusScript ConwayEra ConwayPlutusV1 Plutus 'PlutusV1 ps PlutusScript (BabbagePlutusV2 Plutus 'PlutusV2 ps) -> PlutusScript ConwayEra -> AlonzoScript ConwayEra forall era. PlutusScript era -> AlonzoScript era PlutusScript (PlutusScript ConwayEra -> AlonzoScript ConwayEra) -> PlutusScript ConwayEra -> AlonzoScript ConwayEra forall a b. (a -> b) -> a -> b $ Plutus 'PlutusV2 -> PlutusScript ConwayEra ConwayPlutusV2 Plutus 'PlutusV2 ps scriptPrefixTag :: Script ConwayEra -> ByteString scriptPrefixTag = Script ConwayEra -> ByteString forall era. (AlonzoEraScript era, AlonzoScript era ~ Script era) => Script era -> ByteString alonzoScriptPrefixTag getNativeScript :: Script ConwayEra -> Maybe (NativeScript ConwayEra) getNativeScript = \case TimelockScript Timelock ConwayEra ts -> Timelock ConwayEra -> Maybe (Timelock ConwayEra) forall a. a -> Maybe a Just Timelock ConwayEra ts Script ConwayEra _ -> Maybe (Timelock ConwayEra) Maybe (NativeScript ConwayEra) forall a. Maybe a Nothing fromNativeScript :: NativeScript ConwayEra -> Script ConwayEra fromNativeScript = Timelock ConwayEra -> AlonzoScript ConwayEra NativeScript ConwayEra -> Script ConwayEra forall era. Timelock era -> AlonzoScript era TimelockScript instance AlonzoEraScript ConwayEra where data PlutusScript ConwayEra = ConwayPlutusV1 !(Plutus 'PlutusV1) | ConwayPlutusV2 !(Plutus 'PlutusV2) | ConwayPlutusV3 !(Plutus 'PlutusV3) deriving (PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool (PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool) -> (PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool) -> Eq (PlutusScript ConwayEra) forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool == :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool $c/= :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool /= :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool Eq, Eq (PlutusScript ConwayEra) Eq (PlutusScript ConwayEra) => (PlutusScript ConwayEra -> PlutusScript ConwayEra -> Ordering) -> (PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool) -> (PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool) -> (PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool) -> (PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool) -> (PlutusScript ConwayEra -> PlutusScript ConwayEra -> PlutusScript ConwayEra) -> (PlutusScript ConwayEra -> PlutusScript ConwayEra -> PlutusScript ConwayEra) -> Ord (PlutusScript ConwayEra) PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool PlutusScript ConwayEra -> PlutusScript ConwayEra -> Ordering PlutusScript ConwayEra -> PlutusScript ConwayEra -> PlutusScript ConwayEra 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 :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Ordering compare :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Ordering $c< :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool < :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool $c<= :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool <= :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool $c> :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool > :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool $c>= :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool >= :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> Bool $cmax :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> PlutusScript ConwayEra max :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> PlutusScript ConwayEra $cmin :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> PlutusScript ConwayEra min :: PlutusScript ConwayEra -> PlutusScript ConwayEra -> PlutusScript ConwayEra Ord, Int -> PlutusScript ConwayEra -> ShowS [PlutusScript ConwayEra] -> ShowS PlutusScript ConwayEra -> String (Int -> PlutusScript ConwayEra -> ShowS) -> (PlutusScript ConwayEra -> String) -> ([PlutusScript ConwayEra] -> ShowS) -> Show (PlutusScript ConwayEra) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> PlutusScript ConwayEra -> ShowS showsPrec :: Int -> PlutusScript ConwayEra -> ShowS $cshow :: PlutusScript ConwayEra -> String show :: PlutusScript ConwayEra -> String $cshowList :: [PlutusScript ConwayEra] -> ShowS showList :: [PlutusScript ConwayEra] -> ShowS Show, (forall x. PlutusScript ConwayEra -> Rep (PlutusScript ConwayEra) x) -> (forall x. Rep (PlutusScript ConwayEra) x -> PlutusScript ConwayEra) -> Generic (PlutusScript ConwayEra) forall x. Rep (PlutusScript ConwayEra) x -> PlutusScript ConwayEra forall x. PlutusScript ConwayEra -> Rep (PlutusScript ConwayEra) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. PlutusScript ConwayEra -> Rep (PlutusScript ConwayEra) x from :: forall x. PlutusScript ConwayEra -> Rep (PlutusScript ConwayEra) x $cto :: forall x. Rep (PlutusScript ConwayEra) x -> PlutusScript ConwayEra to :: forall x. Rep (PlutusScript ConwayEra) x -> PlutusScript ConwayEra Generic) type PlutusPurpose f ConwayEra = ConwayPlutusPurpose f ConwayEra eraMaxLanguage :: Language eraMaxLanguage = Language PlutusV3 mkPlutusScript :: forall (l :: Language). PlutusLanguage l => Plutus l -> Maybe (PlutusScript ConwayEra) mkPlutusScript Plutus l plutus = case Plutus l -> SLanguage l forall (l :: Language) (proxy :: Language -> *). PlutusLanguage l => proxy l -> SLanguage l plutusSLanguage Plutus l plutus of SLanguage l SPlutusV1 -> PlutusScript ConwayEra -> Maybe (PlutusScript ConwayEra) forall a. a -> Maybe a Just (PlutusScript ConwayEra -> Maybe (PlutusScript ConwayEra)) -> PlutusScript ConwayEra -> Maybe (PlutusScript ConwayEra) forall a b. (a -> b) -> a -> b $ Plutus 'PlutusV1 -> PlutusScript ConwayEra ConwayPlutusV1 Plutus l Plutus 'PlutusV1 plutus SLanguage l SPlutusV2 -> PlutusScript ConwayEra -> Maybe (PlutusScript ConwayEra) forall a. a -> Maybe a Just (PlutusScript ConwayEra -> Maybe (PlutusScript ConwayEra)) -> PlutusScript ConwayEra -> Maybe (PlutusScript ConwayEra) forall a b. (a -> b) -> a -> b $ Plutus 'PlutusV2 -> PlutusScript ConwayEra ConwayPlutusV2 Plutus l Plutus 'PlutusV2 plutus SLanguage l SPlutusV3 -> PlutusScript ConwayEra -> Maybe (PlutusScript ConwayEra) forall a. a -> Maybe a Just (PlutusScript ConwayEra -> Maybe (PlutusScript ConwayEra)) -> PlutusScript ConwayEra -> Maybe (PlutusScript ConwayEra) forall a b. (a -> b) -> a -> b $ Plutus 'PlutusV3 -> PlutusScript ConwayEra ConwayPlutusV3 Plutus l Plutus 'PlutusV3 plutus withPlutusScript :: forall a. PlutusScript ConwayEra -> (forall (l :: Language). PlutusLanguage l => Plutus l -> a) -> a withPlutusScript (ConwayPlutusV1 Plutus 'PlutusV1 plutus) forall (l :: Language). PlutusLanguage l => Plutus l -> a f = Plutus 'PlutusV1 -> a forall (l :: Language). PlutusLanguage l => Plutus l -> a f Plutus 'PlutusV1 plutus withPlutusScript (ConwayPlutusV2 Plutus 'PlutusV2 plutus) forall (l :: Language). PlutusLanguage l => Plutus l -> a f = Plutus 'PlutusV2 -> a forall (l :: Language). PlutusLanguage l => Plutus l -> a f Plutus 'PlutusV2 plutus withPlutusScript (ConwayPlutusV3 Plutus 'PlutusV3 plutus) forall (l :: Language). PlutusLanguage l => Plutus l -> a f = Plutus 'PlutusV3 -> a forall (l :: Language). PlutusLanguage l => Plutus l -> a f Plutus 'PlutusV3 plutus hoistPlutusPurpose :: forall (g :: * -> * -> *) (f :: * -> * -> *). (forall ix it. g ix it -> f ix it) -> PlutusPurpose g ConwayEra -> PlutusPurpose f ConwayEra hoistPlutusPurpose forall ix it. g ix it -> f ix it f = \case ConwaySpending g Word32 TxIn x -> f Word32 TxIn -> ConwayPlutusPurpose f ConwayEra forall (f :: * -> * -> *) era. f Word32 TxIn -> ConwayPlutusPurpose f era ConwaySpending (f Word32 TxIn -> ConwayPlutusPurpose f ConwayEra) -> f Word32 TxIn -> ConwayPlutusPurpose f ConwayEra forall a b. (a -> b) -> a -> b $ g Word32 TxIn -> f Word32 TxIn forall ix it. g ix it -> f ix it f g Word32 TxIn x ConwayMinting g Word32 PolicyID x -> f Word32 PolicyID -> ConwayPlutusPurpose f ConwayEra forall (f :: * -> * -> *) era. f Word32 PolicyID -> ConwayPlutusPurpose f era ConwayMinting (f Word32 PolicyID -> ConwayPlutusPurpose f ConwayEra) -> f Word32 PolicyID -> ConwayPlutusPurpose f ConwayEra forall a b. (a -> b) -> a -> b $ g Word32 PolicyID -> f Word32 PolicyID forall ix it. g ix it -> f ix it f g Word32 PolicyID x ConwayCertifying g Word32 (TxCert ConwayEra) x -> f Word32 (TxCert ConwayEra) -> ConwayPlutusPurpose f ConwayEra forall (f :: * -> * -> *) era. f Word32 (TxCert era) -> ConwayPlutusPurpose f era ConwayCertifying (f Word32 (TxCert ConwayEra) -> ConwayPlutusPurpose f ConwayEra) -> f Word32 (TxCert ConwayEra) -> ConwayPlutusPurpose f ConwayEra forall a b. (a -> b) -> a -> b $ g Word32 (ConwayTxCert ConwayEra) -> f Word32 (ConwayTxCert ConwayEra) forall ix it. g ix it -> f ix it f g Word32 (TxCert ConwayEra) g Word32 (ConwayTxCert ConwayEra) x ConwayRewarding g Word32 RewardAccount x -> f Word32 RewardAccount -> ConwayPlutusPurpose f ConwayEra forall (f :: * -> * -> *) era. f Word32 RewardAccount -> ConwayPlutusPurpose f era ConwayRewarding (f Word32 RewardAccount -> ConwayPlutusPurpose f ConwayEra) -> f Word32 RewardAccount -> ConwayPlutusPurpose f ConwayEra forall a b. (a -> b) -> a -> b $ g Word32 RewardAccount -> f Word32 RewardAccount forall ix it. g ix it -> f ix it f g Word32 RewardAccount x ConwayVoting g Word32 Voter x -> f Word32 Voter -> ConwayPlutusPurpose f ConwayEra forall (f :: * -> * -> *) era. f Word32 Voter -> ConwayPlutusPurpose f era ConwayVoting (f Word32 Voter -> ConwayPlutusPurpose f ConwayEra) -> f Word32 Voter -> ConwayPlutusPurpose f ConwayEra forall a b. (a -> b) -> a -> b $ g Word32 Voter -> f Word32 Voter forall ix it. g ix it -> f ix it f g Word32 Voter x ConwayProposing g Word32 (ProposalProcedure ConwayEra) x -> f Word32 (ProposalProcedure ConwayEra) -> ConwayPlutusPurpose f ConwayEra forall (f :: * -> * -> *) era. f Word32 (ProposalProcedure era) -> ConwayPlutusPurpose f era ConwayProposing (f Word32 (ProposalProcedure ConwayEra) -> ConwayPlutusPurpose f ConwayEra) -> f Word32 (ProposalProcedure ConwayEra) -> ConwayPlutusPurpose f ConwayEra forall a b. (a -> b) -> a -> b $ g Word32 (ProposalProcedure ConwayEra) -> f Word32 (ProposalProcedure ConwayEra) forall ix it. g ix it -> f ix it f g Word32 (ProposalProcedure ConwayEra) x mkSpendingPurpose :: forall (f :: * -> * -> *). f Word32 TxIn -> PlutusPurpose f ConwayEra mkSpendingPurpose = f Word32 TxIn -> PlutusPurpose f ConwayEra f Word32 TxIn -> ConwayPlutusPurpose f ConwayEra forall (f :: * -> * -> *) era. f Word32 TxIn -> ConwayPlutusPurpose f era ConwaySpending toSpendingPurpose :: forall (f :: * -> * -> *). PlutusPurpose f ConwayEra -> Maybe (f Word32 TxIn) toSpendingPurpose (ConwaySpending f Word32 TxIn i) = f Word32 TxIn -> Maybe (f Word32 TxIn) forall a. a -> Maybe a Just f Word32 TxIn i toSpendingPurpose PlutusPurpose f ConwayEra _ = Maybe (f Word32 TxIn) forall a. Maybe a Nothing mkMintingPurpose :: forall (f :: * -> * -> *). f Word32 PolicyID -> PlutusPurpose f ConwayEra mkMintingPurpose = f Word32 PolicyID -> PlutusPurpose f ConwayEra f Word32 PolicyID -> ConwayPlutusPurpose f ConwayEra forall (f :: * -> * -> *) era. f Word32 PolicyID -> ConwayPlutusPurpose f era ConwayMinting toMintingPurpose :: forall (f :: * -> * -> *). PlutusPurpose f ConwayEra -> Maybe (f Word32 PolicyID) toMintingPurpose (ConwayMinting f Word32 PolicyID i) = f Word32 PolicyID -> Maybe (f Word32 PolicyID) forall a. a -> Maybe a Just f Word32 PolicyID i toMintingPurpose PlutusPurpose f ConwayEra _ = Maybe (f Word32 PolicyID) forall a. Maybe a Nothing mkCertifyingPurpose :: forall (f :: * -> * -> *). f Word32 (TxCert ConwayEra) -> PlutusPurpose f ConwayEra mkCertifyingPurpose = f Word32 (TxCert ConwayEra) -> PlutusPurpose f ConwayEra f Word32 (TxCert ConwayEra) -> ConwayPlutusPurpose f ConwayEra forall (f :: * -> * -> *) era. f Word32 (TxCert era) -> ConwayPlutusPurpose f era ConwayCertifying toCertifyingPurpose :: forall (f :: * -> * -> *). PlutusPurpose f ConwayEra -> Maybe (f Word32 (TxCert ConwayEra)) toCertifyingPurpose (ConwayCertifying f Word32 (TxCert ConwayEra) i) = f Word32 (ConwayTxCert ConwayEra) -> Maybe (f Word32 (ConwayTxCert ConwayEra)) forall a. a -> Maybe a Just f Word32 (TxCert ConwayEra) f Word32 (ConwayTxCert ConwayEra) i toCertifyingPurpose PlutusPurpose f ConwayEra _ = Maybe (f Word32 (TxCert ConwayEra)) Maybe (f Word32 (ConwayTxCert ConwayEra)) forall a. Maybe a Nothing mkRewardingPurpose :: forall (f :: * -> * -> *). f Word32 RewardAccount -> PlutusPurpose f ConwayEra mkRewardingPurpose = f Word32 RewardAccount -> PlutusPurpose f ConwayEra f Word32 RewardAccount -> ConwayPlutusPurpose f ConwayEra forall (f :: * -> * -> *) era. f Word32 RewardAccount -> ConwayPlutusPurpose f era ConwayRewarding toRewardingPurpose :: forall (f :: * -> * -> *). PlutusPurpose f ConwayEra -> Maybe (f Word32 RewardAccount) toRewardingPurpose (ConwayRewarding f Word32 RewardAccount i) = f Word32 RewardAccount -> Maybe (f Word32 RewardAccount) forall a. a -> Maybe a Just f Word32 RewardAccount i toRewardingPurpose PlutusPurpose f ConwayEra _ = Maybe (f Word32 RewardAccount) forall a. Maybe a Nothing upgradePlutusPurposeAsIx :: AlonzoEraScript (PreviousEra ConwayEra) => PlutusPurpose AsIx (PreviousEra ConwayEra) -> PlutusPurpose AsIx ConwayEra upgradePlutusPurposeAsIx = \case AlonzoSpending (AsIx Word32 ix) -> AsIx Word32 TxIn -> ConwayPlutusPurpose AsIx ConwayEra forall (f :: * -> * -> *) era. f Word32 TxIn -> ConwayPlutusPurpose f era ConwaySpending (Word32 -> AsIx Word32 TxIn forall ix it. ix -> AsIx ix it AsIx Word32 ix) AlonzoMinting (AsIx Word32 ix) -> AsIx Word32 PolicyID -> ConwayPlutusPurpose AsIx ConwayEra forall (f :: * -> * -> *) era. f Word32 PolicyID -> ConwayPlutusPurpose f era ConwayMinting (Word32 -> AsIx Word32 PolicyID forall ix it. ix -> AsIx ix it AsIx Word32 ix) AlonzoCertifying (AsIx Word32 ix) -> AsIx Word32 (TxCert ConwayEra) -> ConwayPlutusPurpose AsIx ConwayEra forall (f :: * -> * -> *) era. f Word32 (TxCert era) -> ConwayPlutusPurpose f era ConwayCertifying (Word32 -> AsIx Word32 (ConwayTxCert ConwayEra) forall ix it. ix -> AsIx ix it AsIx Word32 ix) AlonzoRewarding (AsIx Word32 ix) -> AsIx Word32 RewardAccount -> ConwayPlutusPurpose AsIx ConwayEra forall (f :: * -> * -> *) era. f Word32 RewardAccount -> ConwayPlutusPurpose f era ConwayRewarding (Word32 -> AsIx Word32 RewardAccount forall ix it. ix -> AsIx ix it AsIx Word32 ix) instance ConwayEraScript ConwayEra where mkVotingPurpose :: forall (f :: * -> * -> *). f Word32 Voter -> PlutusPurpose f ConwayEra mkVotingPurpose = f Word32 Voter -> PlutusPurpose f ConwayEra f Word32 Voter -> ConwayPlutusPurpose f ConwayEra forall (f :: * -> * -> *) era. f Word32 Voter -> ConwayPlutusPurpose f era ConwayVoting toVotingPurpose :: forall (f :: * -> * -> *). PlutusPurpose f ConwayEra -> Maybe (f Word32 Voter) toVotingPurpose (ConwayVoting f Word32 Voter i) = f Word32 Voter -> Maybe (f Word32 Voter) forall a. a -> Maybe a Just f Word32 Voter i toVotingPurpose PlutusPurpose f ConwayEra _ = Maybe (f Word32 Voter) forall a. Maybe a Nothing mkProposingPurpose :: forall (f :: * -> * -> *). f Word32 (ProposalProcedure ConwayEra) -> PlutusPurpose f ConwayEra mkProposingPurpose = f Word32 (ProposalProcedure ConwayEra) -> PlutusPurpose f ConwayEra f Word32 (ProposalProcedure ConwayEra) -> ConwayPlutusPurpose f ConwayEra forall (f :: * -> * -> *) era. f Word32 (ProposalProcedure era) -> ConwayPlutusPurpose f era ConwayProposing toProposingPurpose :: forall (f :: * -> * -> *). PlutusPurpose f ConwayEra -> Maybe (f Word32 (ProposalProcedure ConwayEra)) toProposingPurpose (ConwayProposing f Word32 (ProposalProcedure ConwayEra) i) = f Word32 (ProposalProcedure ConwayEra) -> Maybe (f Word32 (ProposalProcedure ConwayEra)) forall a. a -> Maybe a Just f Word32 (ProposalProcedure ConwayEra) i toProposingPurpose PlutusPurpose f ConwayEra _ = Maybe (f Word32 (ProposalProcedure ConwayEra)) forall a. Maybe a Nothing instance ShelleyEraScript ConwayEra where mkRequireSignature :: KeyHash 'Witness -> NativeScript ConwayEra mkRequireSignature = KeyHash 'Witness -> Timelock ConwayEra KeyHash 'Witness -> NativeScript ConwayEra forall era. Era era => KeyHash 'Witness -> Timelock era mkRequireSignatureTimelock getRequireSignature :: NativeScript ConwayEra -> Maybe (KeyHash 'Witness) getRequireSignature = Timelock ConwayEra -> Maybe (KeyHash 'Witness) NativeScript ConwayEra -> Maybe (KeyHash 'Witness) forall {k} (era :: k). Timelock era -> Maybe (KeyHash 'Witness) getRequireSignatureTimelock mkRequireAllOf :: StrictSeq (NativeScript ConwayEra) -> NativeScript ConwayEra mkRequireAllOf = StrictSeq (Timelock ConwayEra) -> Timelock ConwayEra StrictSeq (NativeScript ConwayEra) -> NativeScript ConwayEra forall era. Era era => StrictSeq (Timelock era) -> Timelock era mkRequireAllOfTimelock getRequireAllOf :: NativeScript ConwayEra -> Maybe (StrictSeq (NativeScript ConwayEra)) getRequireAllOf = Timelock ConwayEra -> Maybe (StrictSeq (Timelock ConwayEra)) NativeScript ConwayEra -> Maybe (StrictSeq (NativeScript ConwayEra)) forall {k} (era :: k). Timelock era -> Maybe (StrictSeq (Timelock era)) getRequireAllOfTimelock mkRequireAnyOf :: StrictSeq (NativeScript ConwayEra) -> NativeScript ConwayEra mkRequireAnyOf = StrictSeq (Timelock ConwayEra) -> Timelock ConwayEra StrictSeq (NativeScript ConwayEra) -> NativeScript ConwayEra forall era. Era era => StrictSeq (Timelock era) -> Timelock era mkRequireAnyOfTimelock getRequireAnyOf :: NativeScript ConwayEra -> Maybe (StrictSeq (NativeScript ConwayEra)) getRequireAnyOf = Timelock ConwayEra -> Maybe (StrictSeq (Timelock ConwayEra)) NativeScript ConwayEra -> Maybe (StrictSeq (NativeScript ConwayEra)) forall {k} (era :: k). Timelock era -> Maybe (StrictSeq (Timelock era)) getRequireAnyOfTimelock mkRequireMOf :: Int -> StrictSeq (NativeScript ConwayEra) -> NativeScript ConwayEra mkRequireMOf = Int -> StrictSeq (Timelock ConwayEra) -> Timelock ConwayEra Int -> StrictSeq (NativeScript ConwayEra) -> NativeScript ConwayEra forall era. Era era => Int -> StrictSeq (Timelock era) -> Timelock era mkRequireMOfTimelock getRequireMOf :: NativeScript ConwayEra -> Maybe (Int, StrictSeq (NativeScript ConwayEra)) getRequireMOf = Timelock ConwayEra -> Maybe (Int, StrictSeq (Timelock ConwayEra)) NativeScript ConwayEra -> Maybe (Int, StrictSeq (NativeScript ConwayEra)) forall {k} (era :: k). Timelock era -> Maybe (Int, StrictSeq (Timelock era)) getRequireMOfTimelock instance AllegraEraScript ConwayEra where mkTimeStart :: SlotNo -> NativeScript ConwayEra mkTimeStart = SlotNo -> Timelock ConwayEra SlotNo -> NativeScript ConwayEra forall era. Era era => SlotNo -> Timelock era mkTimeStartTimelock getTimeStart :: NativeScript ConwayEra -> Maybe SlotNo getTimeStart = Timelock ConwayEra -> Maybe SlotNo NativeScript ConwayEra -> Maybe SlotNo forall {k} (era :: k). Timelock era -> Maybe SlotNo getTimeStartTimelock mkTimeExpire :: SlotNo -> NativeScript ConwayEra mkTimeExpire = SlotNo -> Timelock ConwayEra SlotNo -> NativeScript ConwayEra forall era. Era era => SlotNo -> Timelock era mkTimeExpireTimelock getTimeExpire :: NativeScript ConwayEra -> Maybe SlotNo getTimeExpire = Timelock ConwayEra -> Maybe SlotNo NativeScript ConwayEra -> Maybe SlotNo forall {k} (era :: k). Timelock era -> Maybe SlotNo getTimeExpireTimelock instance NFData (PlutusScript ConwayEra) where rnf :: PlutusScript ConwayEra -> () rnf = PlutusScript ConwayEra -> () forall a. a -> () rwhnf instance NoThunks (PlutusScript ConwayEra) instance SafeToHash (PlutusScript ConwayEra) where originalBytes :: PlutusScript ConwayEra -> ByteString originalBytes PlutusScript ConwayEra ps = PlutusScript ConwayEra -> (forall (l :: Language). PlutusLanguage l => Plutus l -> ByteString) -> ByteString forall era a. AlonzoEraScript era => PlutusScript era -> (forall (l :: Language). PlutusLanguage l => Plutus l -> a) -> a forall a. PlutusScript ConwayEra -> (forall (l :: Language). PlutusLanguage l => Plutus l -> a) -> a withPlutusScript PlutusScript ConwayEra ps Plutus l -> ByteString forall t. SafeToHash t => t -> ByteString forall (l :: Language). PlutusLanguage l => Plutus l -> ByteString originalBytes instance MemPack (PlutusScript ConwayEra) where packedByteCount :: PlutusScript ConwayEra -> Int packedByteCount = \case ConwayPlutusV1 Plutus 'PlutusV1 script -> Int packedTagByteCount Int -> Int -> Int forall a. Num a => a -> a -> a + Plutus 'PlutusV1 -> Int forall a. MemPack a => a -> Int packedByteCount Plutus 'PlutusV1 script ConwayPlutusV2 Plutus 'PlutusV2 script -> Int packedTagByteCount Int -> Int -> Int forall a. Num a => a -> a -> a + Plutus 'PlutusV2 -> Int forall a. MemPack a => a -> Int packedByteCount Plutus 'PlutusV2 script ConwayPlutusV3 Plutus 'PlutusV3 script -> Int packedTagByteCount Int -> Int -> Int forall a. Num a => a -> a -> a + Plutus 'PlutusV3 -> Int forall a. MemPack a => a -> Int packedByteCount Plutus 'PlutusV3 script packM :: forall s. PlutusScript ConwayEra -> Pack s () packM = \case ConwayPlutusV1 Plutus 'PlutusV1 script -> Tag -> Pack s () forall s. Tag -> Pack s () packTagM Tag 0 Pack s () -> Pack s () -> Pack s () forall a b. Pack s a -> Pack s b -> Pack s b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> Plutus 'PlutusV1 -> Pack s () forall s. Plutus 'PlutusV1 -> Pack s () forall a s. MemPack a => a -> Pack s () packM Plutus 'PlutusV1 script ConwayPlutusV2 Plutus 'PlutusV2 script -> Tag -> Pack s () forall s. Tag -> Pack s () packTagM Tag 1 Pack s () -> Pack s () -> Pack s () forall a b. Pack s a -> Pack s b -> Pack s b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> Plutus 'PlutusV2 -> Pack s () forall s. Plutus 'PlutusV2 -> Pack s () forall a s. MemPack a => a -> Pack s () packM Plutus 'PlutusV2 script ConwayPlutusV3 Plutus 'PlutusV3 script -> Tag -> Pack s () forall s. Tag -> Pack s () packTagM Tag 2 Pack s () -> Pack s () -> Pack s () forall a b. Pack s a -> Pack s b -> Pack s b forall (m :: * -> *) a b. Monad m => m a -> m b -> m b >> Plutus 'PlutusV3 -> Pack s () forall s. Plutus 'PlutusV3 -> Pack s () forall a s. MemPack a => a -> Pack s () packM Plutus 'PlutusV3 script {-# INLINE packM #-} unpackM :: forall b. Buffer b => Unpack b (PlutusScript ConwayEra) unpackM = Unpack b Tag forall b. Buffer b => Unpack b Tag unpackTagM Unpack b Tag -> (Tag -> Unpack b (PlutusScript ConwayEra)) -> Unpack b (PlutusScript ConwayEra) forall a b. Unpack b a -> (a -> Unpack b b) -> Unpack b b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= \case Tag 0 -> Plutus 'PlutusV1 -> PlutusScript ConwayEra ConwayPlutusV1 (Plutus 'PlutusV1 -> PlutusScript ConwayEra) -> Unpack b (Plutus 'PlutusV1) -> Unpack b (PlutusScript ConwayEra) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Unpack b (Plutus 'PlutusV1) forall a b. (MemPack a, Buffer b) => Unpack b a forall b. Buffer b => Unpack b (Plutus 'PlutusV1) unpackM Tag 1 -> Plutus 'PlutusV2 -> PlutusScript ConwayEra ConwayPlutusV2 (Plutus 'PlutusV2 -> PlutusScript ConwayEra) -> Unpack b (Plutus 'PlutusV2) -> Unpack b (PlutusScript ConwayEra) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Unpack b (Plutus 'PlutusV2) forall a b. (MemPack a, Buffer b) => Unpack b a forall b. Buffer b => Unpack b (Plutus 'PlutusV2) unpackM Tag 2 -> Plutus 'PlutusV3 -> PlutusScript ConwayEra ConwayPlutusV3 (Plutus 'PlutusV3 -> PlutusScript ConwayEra) -> Unpack b (Plutus 'PlutusV3) -> Unpack b (PlutusScript ConwayEra) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Unpack b (Plutus 'PlutusV3) forall a b. (MemPack a, Buffer b) => Unpack b a forall b. Buffer b => Unpack b (Plutus 'PlutusV3) unpackM Tag n -> forall a (m :: * -> *) b. (MemPack a, MonadFail m) => Tag -> m b unknownTagM @(PlutusScript ConwayEra) Tag n {-# INLINE unpackM #-} data ConwayPlutusPurpose f era = ConwaySpending !(f Word32 TxIn) | ConwayMinting !(f Word32 PolicyID) | ConwayCertifying !(f Word32 (TxCert era)) | ConwayRewarding !(f Word32 RewardAccount) | ConwayVoting !(f Word32 Voter) | ConwayProposing !(f Word32 (ProposalProcedure era)) deriving ((forall x. ConwayPlutusPurpose f era -> Rep (ConwayPlutusPurpose f era) x) -> (forall x. Rep (ConwayPlutusPurpose f era) x -> ConwayPlutusPurpose f era) -> Generic (ConwayPlutusPurpose f era) forall x. Rep (ConwayPlutusPurpose f era) x -> ConwayPlutusPurpose f era forall x. ConwayPlutusPurpose f era -> Rep (ConwayPlutusPurpose f era) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall (f :: * -> * -> *) era x. Rep (ConwayPlutusPurpose f era) x -> ConwayPlutusPurpose f era forall (f :: * -> * -> *) era x. ConwayPlutusPurpose f era -> Rep (ConwayPlutusPurpose f era) x $cfrom :: forall (f :: * -> * -> *) era x. ConwayPlutusPurpose f era -> Rep (ConwayPlutusPurpose f era) x from :: forall x. ConwayPlutusPurpose f era -> Rep (ConwayPlutusPurpose f era) x $cto :: forall (f :: * -> * -> *) era x. Rep (ConwayPlutusPurpose f era) x -> ConwayPlutusPurpose f era to :: forall x. Rep (ConwayPlutusPurpose f era) x -> ConwayPlutusPurpose f era Generic) deriving instance Eq (ConwayPlutusPurpose AsIx era) deriving instance Ord (ConwayPlutusPurpose AsIx era) deriving instance Show (ConwayPlutusPurpose AsIx era) instance NoThunks (ConwayPlutusPurpose AsIx era) deriving instance (Eq (TxCert era), EraPParams era) => Eq (ConwayPlutusPurpose AsItem era) deriving instance (Show (TxCert era), EraPParams era) => Show (ConwayPlutusPurpose AsItem era) instance (NoThunks (TxCert era), EraPParams era) => NoThunks (ConwayPlutusPurpose AsItem era) deriving via (CBORGroup (ConwayPlutusPurpose f era)) instance ( forall a b. (EncCBOR a, EncCBOR b) => EncCBOR (f a b) , EraPParams era , Typeable f , EncCBOR (TxCert era) ) => EncCBOR (ConwayPlutusPurpose f era) deriving via (CBORGroup (ConwayPlutusPurpose f era)) instance ( forall a b. (EncCBOR a, EncCBOR b) => EncCBOR (f a b) , forall a b. (DecCBOR a, DecCBOR b) => DecCBOR (f a b) , EraPParams era , Typeable f , EncCBOR (TxCert era) , DecCBOR (TxCert era) ) => DecCBOR (ConwayPlutusPurpose f era) deriving instance (Eq (TxCert era), EraPParams era) => Eq (ConwayPlutusPurpose AsIxItem era) deriving instance (Show (TxCert era), EraPParams era) => Show (ConwayPlutusPurpose AsIxItem era) instance (NoThunks (TxCert era), EraPParams era) => NoThunks (ConwayPlutusPurpose AsIxItem era) instance (forall a b. (NFData a, NFData b) => NFData (f a b), NFData (TxCert era), EraPParams era) => NFData (ConwayPlutusPurpose f era) where rnf :: ConwayPlutusPurpose f era -> () rnf = \case ConwaySpending f Word32 TxIn x -> f Word32 TxIn -> () forall a. NFData a => a -> () rnf f Word32 TxIn x ConwayMinting f Word32 PolicyID x -> f Word32 PolicyID -> () forall a. NFData a => a -> () rnf f Word32 PolicyID x ConwayCertifying f Word32 (TxCert era) x -> f Word32 (TxCert era) -> () forall a. NFData a => a -> () rnf f Word32 (TxCert era) x ConwayRewarding f Word32 RewardAccount x -> f Word32 RewardAccount -> () forall a. NFData a => a -> () rnf f Word32 RewardAccount x ConwayVoting f Word32 Voter x -> f Word32 Voter -> () forall a. NFData a => a -> () rnf f Word32 Voter x ConwayProposing f Word32 (ProposalProcedure era) x -> f Word32 (ProposalProcedure era) -> () forall a. NFData a => a -> () rnf f Word32 (ProposalProcedure era) x instance ( forall a b. (EncCBOR a, EncCBOR b) => EncCBOR (f a b) , EraPParams era , Typeable f , EncCBOR (TxCert era) ) => EncCBORGroup (ConwayPlutusPurpose f era) where listLen :: ConwayPlutusPurpose f era -> Word listLen ConwayPlutusPurpose f era _ = Word 2 listLenBound :: Proxy (ConwayPlutusPurpose f era) -> Word listLenBound Proxy (ConwayPlutusPurpose f era) _ = Word 2 encCBORGroup :: ConwayPlutusPurpose f era -> Encoding encCBORGroup = \case ConwaySpending f Word32 TxIn p -> Word8 -> Encoding encodeWord8 Word8 0 Encoding -> Encoding -> Encoding forall a. Semigroup a => a -> a -> a <> f Word32 TxIn -> Encoding forall a. EncCBOR a => a -> Encoding encCBOR f Word32 TxIn p ConwayMinting f Word32 PolicyID p -> Word8 -> Encoding encodeWord8 Word8 1 Encoding -> Encoding -> Encoding forall a. Semigroup a => a -> a -> a <> f Word32 PolicyID -> Encoding forall a. EncCBOR a => a -> Encoding encCBOR f Word32 PolicyID p ConwayCertifying f Word32 (TxCert era) p -> Word8 -> Encoding encodeWord8 Word8 2 Encoding -> Encoding -> Encoding forall a. Semigroup a => a -> a -> a <> f Word32 (TxCert era) -> Encoding forall a. EncCBOR a => a -> Encoding encCBOR f Word32 (TxCert era) p ConwayRewarding f Word32 RewardAccount p -> Word8 -> Encoding encodeWord8 Word8 3 Encoding -> Encoding -> Encoding forall a. Semigroup a => a -> a -> a <> f Word32 RewardAccount -> Encoding forall a. EncCBOR a => a -> Encoding encCBOR f Word32 RewardAccount p ConwayVoting f Word32 Voter p -> Word8 -> Encoding encodeWord8 Word8 4 Encoding -> Encoding -> Encoding forall a. Semigroup a => a -> a -> a <> f Word32 Voter -> Encoding forall a. EncCBOR a => a -> Encoding encCBOR f Word32 Voter p ConwayProposing f Word32 (ProposalProcedure era) p -> Word8 -> Encoding encodeWord8 Word8 5 Encoding -> Encoding -> Encoding forall a. Semigroup a => a -> a -> a <> f Word32 (ProposalProcedure era) -> Encoding forall a. EncCBOR a => a -> Encoding encCBOR f Word32 (ProposalProcedure era) p encodedGroupSizeExpr :: (forall t. EncCBOR t => Proxy t -> Size) -> Proxy (ConwayPlutusPurpose f era) -> Size encodedGroupSizeExpr forall t. EncCBOR t => Proxy t -> Size size_ Proxy (ConwayPlutusPurpose f era) _proxy = (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Word8 -> Size forall a. EncCBOR a => (forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size encodedSizeExpr Proxy t -> Size forall t. EncCBOR t => Proxy t -> Size size_ (Proxy Word8 forall {k} (t :: k). Proxy t Proxy :: Proxy Word8) Size -> Size -> Size forall a. Num a => a -> a -> a + (forall t. EncCBOR t => Proxy t -> Size) -> Proxy Word16 -> Size forall a. EncCBOR a => (forall t. EncCBOR t => Proxy t -> Size) -> Proxy a -> Size encodedSizeExpr Proxy t -> Size forall t. EncCBOR t => Proxy t -> Size size_ (Proxy Word16 forall {k} (t :: k). Proxy t Proxy :: Proxy Word16) instance ( forall a b. (DecCBOR a, DecCBOR b) => DecCBOR (f a b) , EraPParams era , Typeable f , DecCBOR (TxCert era) ) => DecCBORGroup (ConwayPlutusPurpose f era) where decCBORGroup :: forall s. Decoder s (ConwayPlutusPurpose f era) decCBORGroup = Decoder s Word8 forall s. Decoder s Word8 decodeWord8 Decoder s Word8 -> (Word8 -> Decoder s (ConwayPlutusPurpose f era)) -> Decoder s (ConwayPlutusPurpose f era) forall a b. Decoder s a -> (a -> Decoder s b) -> Decoder s b forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b >>= \case Word8 0 -> f Word32 TxIn -> ConwayPlutusPurpose f era forall (f :: * -> * -> *) era. f Word32 TxIn -> ConwayPlutusPurpose f era ConwaySpending (f Word32 TxIn -> ConwayPlutusPurpose f era) -> Decoder s (f Word32 TxIn) -> Decoder s (ConwayPlutusPurpose f era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Decoder s (f Word32 TxIn) forall s. Decoder s (f Word32 TxIn) forall a s. DecCBOR a => Decoder s a decCBOR Word8 1 -> f Word32 PolicyID -> ConwayPlutusPurpose f era forall (f :: * -> * -> *) era. f Word32 PolicyID -> ConwayPlutusPurpose f era ConwayMinting (f Word32 PolicyID -> ConwayPlutusPurpose f era) -> Decoder s (f Word32 PolicyID) -> Decoder s (ConwayPlutusPurpose f era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Decoder s (f Word32 PolicyID) forall s. Decoder s (f Word32 PolicyID) forall a s. DecCBOR a => Decoder s a decCBOR Word8 2 -> f Word32 (TxCert era) -> ConwayPlutusPurpose f era forall (f :: * -> * -> *) era. f Word32 (TxCert era) -> ConwayPlutusPurpose f era ConwayCertifying (f Word32 (TxCert era) -> ConwayPlutusPurpose f era) -> Decoder s (f Word32 (TxCert era)) -> Decoder s (ConwayPlutusPurpose f era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Decoder s (f Word32 (TxCert era)) forall s. Decoder s (f Word32 (TxCert era)) forall a s. DecCBOR a => Decoder s a decCBOR Word8 3 -> f Word32 RewardAccount -> ConwayPlutusPurpose f era forall (f :: * -> * -> *) era. f Word32 RewardAccount -> ConwayPlutusPurpose f era ConwayRewarding (f Word32 RewardAccount -> ConwayPlutusPurpose f era) -> Decoder s (f Word32 RewardAccount) -> Decoder s (ConwayPlutusPurpose f era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Decoder s (f Word32 RewardAccount) forall s. Decoder s (f Word32 RewardAccount) forall a s. DecCBOR a => Decoder s a decCBOR Word8 4 -> f Word32 Voter -> ConwayPlutusPurpose f era forall (f :: * -> * -> *) era. f Word32 Voter -> ConwayPlutusPurpose f era ConwayVoting (f Word32 Voter -> ConwayPlutusPurpose f era) -> Decoder s (f Word32 Voter) -> Decoder s (ConwayPlutusPurpose f era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Decoder s (f Word32 Voter) forall s. Decoder s (f Word32 Voter) forall a s. DecCBOR a => Decoder s a decCBOR Word8 5 -> f Word32 (ProposalProcedure era) -> ConwayPlutusPurpose f era forall (f :: * -> * -> *) era. f Word32 (ProposalProcedure era) -> ConwayPlutusPurpose f era ConwayProposing (f Word32 (ProposalProcedure era) -> ConwayPlutusPurpose f era) -> Decoder s (f Word32 (ProposalProcedure era)) -> Decoder s (ConwayPlutusPurpose f era) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Decoder s (f Word32 (ProposalProcedure era)) forall s. Decoder s (f Word32 (ProposalProcedure era)) forall a s. DecCBOR a => Decoder s a decCBOR Word8 n -> String -> Decoder s (ConwayPlutusPurpose f era) forall a. String -> Decoder s a forall (m :: * -> *) a. MonadFail m => String -> m a fail (String -> Decoder s (ConwayPlutusPurpose f era)) -> String -> Decoder s (ConwayPlutusPurpose f era) forall a b. (a -> b) -> a -> b $ String "Unexpected tag for ConwayPlutusPurpose: " String -> ShowS forall a. Semigroup a => a -> a -> a <> Word8 -> String forall a. Show a => a -> String show Word8 n instance ( forall a b. (ToJSON a, ToJSON b) => ToJSON (f a b) , ToJSON (TxCert era) , EraPParams era ) => ToJSON (ConwayPlutusPurpose f era) where toJSON :: ConwayPlutusPurpose f era -> Value toJSON = \case ConwaySpending f Word32 TxIn n -> Text -> f Word32 TxIn -> Value forall {v}. ToJSON v => Text -> v -> Value kindObjectWithValue Text "ConwaySpending" f Word32 TxIn n ConwayMinting f Word32 PolicyID n -> Text -> f Word32 PolicyID -> Value forall {v}. ToJSON v => Text -> v -> Value kindObjectWithValue Text "ConwayMinting" f Word32 PolicyID n ConwayCertifying f Word32 (TxCert era) n -> Text -> f Word32 (TxCert era) -> Value forall {v}. ToJSON v => Text -> v -> Value kindObjectWithValue Text "ConwayCertifying" f Word32 (TxCert era) n ConwayRewarding f Word32 RewardAccount n -> Text -> f Word32 RewardAccount -> Value forall {v}. ToJSON v => Text -> v -> Value kindObjectWithValue Text "ConwayRewarding" f Word32 RewardAccount n ConwayVoting f Word32 Voter n -> Text -> f Word32 Voter -> Value forall {v}. ToJSON v => Text -> v -> Value kindObjectWithValue Text "ConwayVoting" f Word32 Voter n ConwayProposing f Word32 (ProposalProcedure era) n -> Text -> f Word32 (ProposalProcedure era) -> Value forall {v}. ToJSON v => Text -> v -> Value kindObjectWithValue Text "ConwayProposing" f Word32 (ProposalProcedure era) n where kindObjectWithValue :: Text -> v -> Value kindObjectWithValue Text name v n = Text -> [Pair] -> Value kindObject Text name [Key "value" Key -> v -> Pair forall v. ToJSON v => Key -> v -> Pair forall e kv v. (KeyValue e kv, ToJSON v) => Key -> v -> kv .= v n] pattern VotingPurpose :: ConwayEraScript era => f Word32 Voter -> PlutusPurpose f era pattern $mVotingPurpose :: forall {r} {era} {f :: * -> * -> *}. ConwayEraScript era => PlutusPurpose f era -> (f Word32 Voter -> r) -> ((# #) -> r) -> r $bVotingPurpose :: forall era (f :: * -> * -> *). ConwayEraScript era => f Word32 Voter -> PlutusPurpose f era VotingPurpose c <- (toVotingPurpose -> Just c) where VotingPurpose f Word32 Voter c = f Word32 Voter -> PlutusPurpose f era forall era (f :: * -> * -> *). ConwayEraScript era => f Word32 Voter -> PlutusPurpose f era forall (f :: * -> * -> *). f Word32 Voter -> PlutusPurpose f era mkVotingPurpose f Word32 Voter c pattern ProposingPurpose :: ConwayEraScript era => f Word32 (ProposalProcedure era) -> PlutusPurpose f era pattern $mProposingPurpose :: forall {r} {era} {f :: * -> * -> *}. ConwayEraScript era => PlutusPurpose f era -> (f Word32 (ProposalProcedure era) -> r) -> ((# #) -> r) -> r $bProposingPurpose :: forall era (f :: * -> * -> *). ConwayEraScript era => f Word32 (ProposalProcedure era) -> PlutusPurpose f era ProposingPurpose c <- (toProposingPurpose -> Just c) where ProposingPurpose f Word32 (ProposalProcedure era) c = f Word32 (ProposalProcedure era) -> PlutusPurpose f era forall era (f :: * -> * -> *). ConwayEraScript era => f Word32 (ProposalProcedure era) -> PlutusPurpose f era forall (f :: * -> * -> *). f Word32 (ProposalProcedure era) -> PlutusPurpose f era mkProposingPurpose f Word32 (ProposalProcedure era) c