{-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE LambdaCase #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -Wno-orphans #-} module Cardano.Ledger.Dijkstra.Scripts (PlutusScript (..)) where import Cardano.Ledger.Allegra.Scripts ( AllegraEraScript (..), Timelock, getRequireAllOfTimelock, getRequireAnyOfTimelock, getRequireMOfTimelock, getRequireSignatureTimelock, getTimeExpireTimelock, getTimeStartTimelock, mkRequireAllOfTimelock, mkRequireAnyOfTimelock, mkRequireMOfTimelock, mkRequireSignatureTimelock, mkTimeExpireTimelock, mkTimeStartTimelock, translateTimelock, ) import Cardano.Ledger.Alonzo (AlonzoScript) import Cardano.Ledger.Alonzo.Scripts ( AlonzoEraScript (..), AlonzoScript (..), AsIx (..), alonzoScriptPrefixTag, ) import Cardano.Ledger.Conway.Scripts ( ConwayEraScript (..), ConwayPlutusPurpose (..), PlutusScript (..), ) import Cardano.Ledger.Core (EraScript (..), SafeToHash (..)) import Cardano.Ledger.Dijkstra.Era (DijkstraEra) import Cardano.Ledger.Dijkstra.PParams () import Cardano.Ledger.Dijkstra.TxCert () import Cardano.Ledger.Plutus (Language (..), Plutus, SLanguage (..), plutusSLanguage) import Cardano.Ledger.Shelley.Scripts (ShelleyEraScript (..)) import Control.DeepSeq (NFData (..), rwhnf) import Data.MemPack (MemPack (..), packTagM, packedTagByteCount, unknownTagM, unpackTagM) import GHC.Generics (Generic) import NoThunks.Class (NoThunks) instance EraScript DijkstraEra where type Script DijkstraEra = AlonzoScript DijkstraEra type NativeScript DijkstraEra = Timelock DijkstraEra upgradeScript :: EraScript (PreviousEra DijkstraEra) => Script (PreviousEra DijkstraEra) -> Script DijkstraEra upgradeScript = \case TimelockScript Timelock ConwayEra ts -> Timelock DijkstraEra -> AlonzoScript DijkstraEra forall era. Timelock era -> AlonzoScript era TimelockScript (Timelock DijkstraEra -> AlonzoScript DijkstraEra) -> Timelock DijkstraEra -> AlonzoScript DijkstraEra forall a b. (a -> b) -> a -> b $ Timelock ConwayEra -> Timelock DijkstraEra forall era1 era2. (Era era1, Era era2) => Timelock era1 -> Timelock era2 translateTimelock Timelock ConwayEra ts PlutusScript (ConwayPlutusV1 Plutus 'PlutusV1 s) -> PlutusScript DijkstraEra -> AlonzoScript DijkstraEra forall era. PlutusScript era -> AlonzoScript era PlutusScript (PlutusScript DijkstraEra -> AlonzoScript DijkstraEra) -> PlutusScript DijkstraEra -> AlonzoScript DijkstraEra forall a b. (a -> b) -> a -> b $ Plutus 'PlutusV1 -> PlutusScript DijkstraEra DijkstraPlutusV1 Plutus 'PlutusV1 s PlutusScript (ConwayPlutusV2 Plutus 'PlutusV2 s) -> PlutusScript DijkstraEra -> AlonzoScript DijkstraEra forall era. PlutusScript era -> AlonzoScript era PlutusScript (PlutusScript DijkstraEra -> AlonzoScript DijkstraEra) -> PlutusScript DijkstraEra -> AlonzoScript DijkstraEra forall a b. (a -> b) -> a -> b $ Plutus 'PlutusV2 -> PlutusScript DijkstraEra DijkstraPlutusV2 Plutus 'PlutusV2 s PlutusScript (ConwayPlutusV3 Plutus 'PlutusV3 s) -> PlutusScript DijkstraEra -> AlonzoScript DijkstraEra forall era. PlutusScript era -> AlonzoScript era PlutusScript (PlutusScript DijkstraEra -> AlonzoScript DijkstraEra) -> PlutusScript DijkstraEra -> AlonzoScript DijkstraEra forall a b. (a -> b) -> a -> b $ Plutus 'PlutusV3 -> PlutusScript DijkstraEra DijkstraPlutusV3 Plutus 'PlutusV3 s scriptPrefixTag :: Script DijkstraEra -> ByteString scriptPrefixTag = Script DijkstraEra -> ByteString forall era. (AlonzoEraScript era, AlonzoScript era ~ Script era) => Script era -> ByteString alonzoScriptPrefixTag getNativeScript :: Script DijkstraEra -> Maybe (NativeScript DijkstraEra) getNativeScript (TimelockScript Timelock DijkstraEra ts) = Timelock DijkstraEra -> Maybe (Timelock DijkstraEra) forall a. a -> Maybe a Just Timelock DijkstraEra ts getNativeScript Script DijkstraEra _ = Maybe (Timelock DijkstraEra) Maybe (NativeScript DijkstraEra) forall a. Maybe a Nothing fromNativeScript :: NativeScript DijkstraEra -> Script DijkstraEra fromNativeScript = Timelock DijkstraEra -> AlonzoScript DijkstraEra NativeScript DijkstraEra -> Script DijkstraEra forall era. Timelock era -> AlonzoScript era TimelockScript instance MemPack (PlutusScript DijkstraEra) where packedByteCount :: PlutusScript DijkstraEra -> Int packedByteCount = \case DijkstraPlutusV1 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 DijkstraPlutusV2 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 DijkstraPlutusV3 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 DijkstraPlutusV4 Plutus 'PlutusV4 script -> Int packedTagByteCount Int -> Int -> Int forall a. Num a => a -> a -> a + Plutus 'PlutusV4 -> Int forall a. MemPack a => a -> Int packedByteCount Plutus 'PlutusV4 script packM :: forall s. PlutusScript DijkstraEra -> Pack s () packM = \case DijkstraPlutusV1 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 DijkstraPlutusV2 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 DijkstraPlutusV3 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 DijkstraPlutusV4 Plutus 'PlutusV4 script -> Tag -> Pack s () forall s. Tag -> Pack s () packTagM Tag 3 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 'PlutusV4 -> Pack s () forall s. Plutus 'PlutusV4 -> Pack s () forall a s. MemPack a => a -> Pack s () packM Plutus 'PlutusV4 script {-# INLINE packM #-} unpackM :: forall b. Buffer b => Unpack b (PlutusScript DijkstraEra) unpackM = Unpack b Tag forall b. Buffer b => Unpack b Tag unpackTagM Unpack b Tag -> (Tag -> Unpack b (PlutusScript DijkstraEra)) -> Unpack b (PlutusScript DijkstraEra) 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 DijkstraEra DijkstraPlutusV1 (Plutus 'PlutusV1 -> PlutusScript DijkstraEra) -> Unpack b (Plutus 'PlutusV1) -> Unpack b (PlutusScript DijkstraEra) 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 DijkstraEra DijkstraPlutusV2 (Plutus 'PlutusV2 -> PlutusScript DijkstraEra) -> Unpack b (Plutus 'PlutusV2) -> Unpack b (PlutusScript DijkstraEra) 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 DijkstraEra DijkstraPlutusV3 (Plutus 'PlutusV3 -> PlutusScript DijkstraEra) -> Unpack b (Plutus 'PlutusV3) -> Unpack b (PlutusScript DijkstraEra) 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 3 -> Plutus 'PlutusV4 -> PlutusScript DijkstraEra DijkstraPlutusV4 (Plutus 'PlutusV4 -> PlutusScript DijkstraEra) -> Unpack b (Plutus 'PlutusV4) -> Unpack b (PlutusScript DijkstraEra) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> Unpack b (Plutus 'PlutusV4) forall a b. (MemPack a, Buffer b) => Unpack b a forall b. Buffer b => Unpack b (Plutus 'PlutusV4) unpackM Tag n -> forall a (m :: * -> *) b. (MemPack a, MonadFail m) => Tag -> m b unknownTagM @(PlutusScript DijkstraEra) Tag n {-# INLINE unpackM #-} instance NFData (PlutusScript DijkstraEra) where rnf :: PlutusScript DijkstraEra -> () rnf = PlutusScript DijkstraEra -> () forall a. a -> () rwhnf instance NoThunks (PlutusScript DijkstraEra) instance SafeToHash (PlutusScript DijkstraEra) where originalBytes :: PlutusScript DijkstraEra -> ByteString originalBytes PlutusScript DijkstraEra ps = PlutusScript DijkstraEra -> (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 DijkstraEra -> (forall (l :: Language). PlutusLanguage l => Plutus l -> a) -> a withPlutusScript PlutusScript DijkstraEra ps Plutus l -> ByteString forall t. SafeToHash t => t -> ByteString forall (l :: Language). PlutusLanguage l => Plutus l -> ByteString originalBytes instance AlonzoEraScript DijkstraEra where data PlutusScript DijkstraEra = DijkstraPlutusV1 !(Plutus 'PlutusV1) | DijkstraPlutusV2 !(Plutus 'PlutusV2) | DijkstraPlutusV3 !(Plutus 'PlutusV3) | DijkstraPlutusV4 !(Plutus 'PlutusV4) deriving (PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool (PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool) -> (PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool) -> Eq (PlutusScript DijkstraEra) forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool == :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool $c/= :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool /= :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool Eq, Eq (PlutusScript DijkstraEra) Eq (PlutusScript DijkstraEra) => (PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Ordering) -> (PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool) -> (PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool) -> (PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool) -> (PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool) -> (PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> PlutusScript DijkstraEra) -> (PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> PlutusScript DijkstraEra) -> Ord (PlutusScript DijkstraEra) PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Ordering PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> PlutusScript DijkstraEra 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 DijkstraEra -> PlutusScript DijkstraEra -> Ordering compare :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Ordering $c< :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool < :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool $c<= :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool <= :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool $c> :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool > :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool $c>= :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool >= :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> Bool $cmax :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> PlutusScript DijkstraEra max :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> PlutusScript DijkstraEra $cmin :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> PlutusScript DijkstraEra min :: PlutusScript DijkstraEra -> PlutusScript DijkstraEra -> PlutusScript DijkstraEra Ord, Int -> PlutusScript DijkstraEra -> ShowS [PlutusScript DijkstraEra] -> ShowS PlutusScript DijkstraEra -> String (Int -> PlutusScript DijkstraEra -> ShowS) -> (PlutusScript DijkstraEra -> String) -> ([PlutusScript DijkstraEra] -> ShowS) -> Show (PlutusScript DijkstraEra) forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: Int -> PlutusScript DijkstraEra -> ShowS showsPrec :: Int -> PlutusScript DijkstraEra -> ShowS $cshow :: PlutusScript DijkstraEra -> String show :: PlutusScript DijkstraEra -> String $cshowList :: [PlutusScript DijkstraEra] -> ShowS showList :: [PlutusScript DijkstraEra] -> ShowS Show, (forall x. PlutusScript DijkstraEra -> Rep (PlutusScript DijkstraEra) x) -> (forall x. Rep (PlutusScript DijkstraEra) x -> PlutusScript DijkstraEra) -> Generic (PlutusScript DijkstraEra) forall x. Rep (PlutusScript DijkstraEra) x -> PlutusScript DijkstraEra forall x. PlutusScript DijkstraEra -> Rep (PlutusScript DijkstraEra) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a $cfrom :: forall x. PlutusScript DijkstraEra -> Rep (PlutusScript DijkstraEra) x from :: forall x. PlutusScript DijkstraEra -> Rep (PlutusScript DijkstraEra) x $cto :: forall x. Rep (PlutusScript DijkstraEra) x -> PlutusScript DijkstraEra to :: forall x. Rep (PlutusScript DijkstraEra) x -> PlutusScript DijkstraEra Generic) type PlutusPurpose f DijkstraEra = ConwayPlutusPurpose f DijkstraEra eraMaxLanguage :: Language eraMaxLanguage = Language PlutusV3 mkPlutusScript :: forall (l :: Language) (m :: * -> *). (PlutusLanguage l, MonadFail m) => Plutus l -> m (PlutusScript DijkstraEra) 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 DijkstraEra -> m (PlutusScript DijkstraEra) forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure (PlutusScript DijkstraEra -> m (PlutusScript DijkstraEra)) -> PlutusScript DijkstraEra -> m (PlutusScript DijkstraEra) forall a b. (a -> b) -> a -> b $ Plutus 'PlutusV1 -> PlutusScript DijkstraEra DijkstraPlutusV1 Plutus l Plutus 'PlutusV1 plutus SLanguage l SPlutusV2 -> PlutusScript DijkstraEra -> m (PlutusScript DijkstraEra) forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure (PlutusScript DijkstraEra -> m (PlutusScript DijkstraEra)) -> PlutusScript DijkstraEra -> m (PlutusScript DijkstraEra) forall a b. (a -> b) -> a -> b $ Plutus 'PlutusV2 -> PlutusScript DijkstraEra DijkstraPlutusV2 Plutus l Plutus 'PlutusV2 plutus SLanguage l SPlutusV3 -> PlutusScript DijkstraEra -> m (PlutusScript DijkstraEra) forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure (PlutusScript DijkstraEra -> m (PlutusScript DijkstraEra)) -> PlutusScript DijkstraEra -> m (PlutusScript DijkstraEra) forall a b. (a -> b) -> a -> b $ Plutus 'PlutusV3 -> PlutusScript DijkstraEra DijkstraPlutusV3 Plutus l Plutus 'PlutusV3 plutus SLanguage l SPlutusV4 -> PlutusScript DijkstraEra -> m (PlutusScript DijkstraEra) forall a. a -> m a forall (f :: * -> *) a. Applicative f => a -> f a pure (PlutusScript DijkstraEra -> m (PlutusScript DijkstraEra)) -> PlutusScript DijkstraEra -> m (PlutusScript DijkstraEra) forall a b. (a -> b) -> a -> b $ Plutus 'PlutusV4 -> PlutusScript DijkstraEra DijkstraPlutusV4 Plutus l Plutus 'PlutusV4 plutus withPlutusScript :: forall a. PlutusScript DijkstraEra -> (forall (l :: Language). PlutusLanguage l => Plutus l -> a) -> a withPlutusScript (DijkstraPlutusV1 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 (DijkstraPlutusV2 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 (DijkstraPlutusV3 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 withPlutusScript (DijkstraPlutusV4 Plutus 'PlutusV4 plutus) forall (l :: Language). PlutusLanguage l => Plutus l -> a f = Plutus 'PlutusV4 -> a forall (l :: Language). PlutusLanguage l => Plutus l -> a f Plutus 'PlutusV4 plutus hoistPlutusPurpose :: forall (g :: * -> * -> *) (f :: * -> * -> *). (forall ix it. g ix it -> f ix it) -> PlutusPurpose g DijkstraEra -> PlutusPurpose f DijkstraEra hoistPlutusPurpose forall ix it. g ix it -> f ix it f = \case ConwaySpending g Word32 TxIn x -> f Word32 TxIn -> ConwayPlutusPurpose f DijkstraEra forall (f :: * -> * -> *) era. f Word32 TxIn -> ConwayPlutusPurpose f era ConwaySpending (f Word32 TxIn -> ConwayPlutusPurpose f DijkstraEra) -> f Word32 TxIn -> ConwayPlutusPurpose f DijkstraEra 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 DijkstraEra forall (f :: * -> * -> *) era. f Word32 PolicyID -> ConwayPlutusPurpose f era ConwayMinting (f Word32 PolicyID -> ConwayPlutusPurpose f DijkstraEra) -> f Word32 PolicyID -> ConwayPlutusPurpose f DijkstraEra 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 DijkstraEra) x -> f Word32 (TxCert DijkstraEra) -> ConwayPlutusPurpose f DijkstraEra forall (f :: * -> * -> *) era. f Word32 (TxCert era) -> ConwayPlutusPurpose f era ConwayCertifying (f Word32 (TxCert DijkstraEra) -> ConwayPlutusPurpose f DijkstraEra) -> f Word32 (TxCert DijkstraEra) -> ConwayPlutusPurpose f DijkstraEra forall a b. (a -> b) -> a -> b $ g Word32 (ConwayTxCert DijkstraEra) -> f Word32 (ConwayTxCert DijkstraEra) forall ix it. g ix it -> f ix it f g Word32 (TxCert DijkstraEra) g Word32 (ConwayTxCert DijkstraEra) x ConwayRewarding g Word32 RewardAccount x -> f Word32 RewardAccount -> ConwayPlutusPurpose f DijkstraEra forall (f :: * -> * -> *) era. f Word32 RewardAccount -> ConwayPlutusPurpose f era ConwayRewarding (f Word32 RewardAccount -> ConwayPlutusPurpose f DijkstraEra) -> f Word32 RewardAccount -> ConwayPlutusPurpose f DijkstraEra 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 DijkstraEra forall (f :: * -> * -> *) era. f Word32 Voter -> ConwayPlutusPurpose f era ConwayVoting (f Word32 Voter -> ConwayPlutusPurpose f DijkstraEra) -> f Word32 Voter -> ConwayPlutusPurpose f DijkstraEra 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 DijkstraEra) x -> f Word32 (ProposalProcedure DijkstraEra) -> ConwayPlutusPurpose f DijkstraEra forall (f :: * -> * -> *) era. f Word32 (ProposalProcedure era) -> ConwayPlutusPurpose f era ConwayProposing (f Word32 (ProposalProcedure DijkstraEra) -> ConwayPlutusPurpose f DijkstraEra) -> f Word32 (ProposalProcedure DijkstraEra) -> ConwayPlutusPurpose f DijkstraEra forall a b. (a -> b) -> a -> b $ g Word32 (ProposalProcedure DijkstraEra) -> f Word32 (ProposalProcedure DijkstraEra) forall ix it. g ix it -> f ix it f g Word32 (ProposalProcedure DijkstraEra) x mkSpendingPurpose :: forall (f :: * -> * -> *). f Word32 TxIn -> PlutusPurpose f DijkstraEra mkSpendingPurpose = f Word32 TxIn -> PlutusPurpose f DijkstraEra f Word32 TxIn -> ConwayPlutusPurpose f DijkstraEra forall (f :: * -> * -> *) era. f Word32 TxIn -> ConwayPlutusPurpose f era ConwaySpending toSpendingPurpose :: forall (f :: * -> * -> *). PlutusPurpose f DijkstraEra -> 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 DijkstraEra _ = Maybe (f Word32 TxIn) forall a. Maybe a Nothing mkMintingPurpose :: forall (f :: * -> * -> *). f Word32 PolicyID -> PlutusPurpose f DijkstraEra mkMintingPurpose = f Word32 PolicyID -> PlutusPurpose f DijkstraEra f Word32 PolicyID -> ConwayPlutusPurpose f DijkstraEra forall (f :: * -> * -> *) era. f Word32 PolicyID -> ConwayPlutusPurpose f era ConwayMinting toMintingPurpose :: forall (f :: * -> * -> *). PlutusPurpose f DijkstraEra -> 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 DijkstraEra _ = Maybe (f Word32 PolicyID) forall a. Maybe a Nothing mkCertifyingPurpose :: forall (f :: * -> * -> *). f Word32 (TxCert DijkstraEra) -> PlutusPurpose f DijkstraEra mkCertifyingPurpose = f Word32 (TxCert DijkstraEra) -> PlutusPurpose f DijkstraEra f Word32 (TxCert DijkstraEra) -> ConwayPlutusPurpose f DijkstraEra forall (f :: * -> * -> *) era. f Word32 (TxCert era) -> ConwayPlutusPurpose f era ConwayCertifying toCertifyingPurpose :: forall (f :: * -> * -> *). PlutusPurpose f DijkstraEra -> Maybe (f Word32 (TxCert DijkstraEra)) toCertifyingPurpose (ConwayCertifying f Word32 (TxCert DijkstraEra) i) = f Word32 (ConwayTxCert DijkstraEra) -> Maybe (f Word32 (ConwayTxCert DijkstraEra)) forall a. a -> Maybe a Just f Word32 (TxCert DijkstraEra) f Word32 (ConwayTxCert DijkstraEra) i toCertifyingPurpose PlutusPurpose f DijkstraEra _ = Maybe (f Word32 (TxCert DijkstraEra)) Maybe (f Word32 (ConwayTxCert DijkstraEra)) forall a. Maybe a Nothing mkRewardingPurpose :: forall (f :: * -> * -> *). f Word32 RewardAccount -> PlutusPurpose f DijkstraEra mkRewardingPurpose = f Word32 RewardAccount -> PlutusPurpose f DijkstraEra f Word32 RewardAccount -> ConwayPlutusPurpose f DijkstraEra forall (f :: * -> * -> *) era. f Word32 RewardAccount -> ConwayPlutusPurpose f era ConwayRewarding toRewardingPurpose :: forall (f :: * -> * -> *). PlutusPurpose f DijkstraEra -> 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 DijkstraEra _ = Maybe (f Word32 RewardAccount) forall a. Maybe a Nothing upgradePlutusPurposeAsIx :: AlonzoEraScript (PreviousEra DijkstraEra) => PlutusPurpose AsIx (PreviousEra DijkstraEra) -> PlutusPurpose AsIx DijkstraEra upgradePlutusPurposeAsIx = \case ConwaySpending (AsIx Word32 ix) -> AsIx Word32 TxIn -> ConwayPlutusPurpose AsIx DijkstraEra forall (f :: * -> * -> *) era. f Word32 TxIn -> ConwayPlutusPurpose f era ConwaySpending (Word32 -> AsIx Word32 TxIn forall ix it. ix -> AsIx ix it AsIx Word32 ix) ConwayMinting (AsIx Word32 ix) -> AsIx Word32 PolicyID -> ConwayPlutusPurpose AsIx DijkstraEra forall (f :: * -> * -> *) era. f Word32 PolicyID -> ConwayPlutusPurpose f era ConwayMinting (Word32 -> AsIx Word32 PolicyID forall ix it. ix -> AsIx ix it AsIx Word32 ix) ConwayCertifying (AsIx Word32 ix) -> AsIx Word32 (TxCert DijkstraEra) -> ConwayPlutusPurpose AsIx DijkstraEra forall (f :: * -> * -> *) era. f Word32 (TxCert era) -> ConwayPlutusPurpose f era ConwayCertifying (Word32 -> AsIx Word32 (ConwayTxCert DijkstraEra) forall ix it. ix -> AsIx ix it AsIx Word32 ix) ConwayRewarding (AsIx Word32 ix) -> AsIx Word32 RewardAccount -> ConwayPlutusPurpose AsIx DijkstraEra forall (f :: * -> * -> *) era. f Word32 RewardAccount -> ConwayPlutusPurpose f era ConwayRewarding (Word32 -> AsIx Word32 RewardAccount forall ix it. ix -> AsIx ix it AsIx Word32 ix) ConwayVoting (AsIx Word32 ix) -> AsIx Word32 Voter -> ConwayPlutusPurpose AsIx DijkstraEra forall (f :: * -> * -> *) era. f Word32 Voter -> ConwayPlutusPurpose f era ConwayVoting (Word32 -> AsIx Word32 Voter forall ix it. ix -> AsIx ix it AsIx Word32 ix) ConwayProposing (AsIx Word32 ix) -> AsIx Word32 (ProposalProcedure DijkstraEra) -> ConwayPlutusPurpose AsIx DijkstraEra forall (f :: * -> * -> *) era. f Word32 (ProposalProcedure era) -> ConwayPlutusPurpose f era ConwayProposing (Word32 -> AsIx Word32 (ProposalProcedure DijkstraEra) forall ix it. ix -> AsIx ix it AsIx Word32 ix) instance ConwayEraScript DijkstraEra where mkVotingPurpose :: forall (f :: * -> * -> *). f Word32 Voter -> PlutusPurpose f DijkstraEra mkVotingPurpose = f Word32 Voter -> PlutusPurpose f DijkstraEra f Word32 Voter -> ConwayPlutusPurpose f DijkstraEra forall (f :: * -> * -> *) era. f Word32 Voter -> ConwayPlutusPurpose f era ConwayVoting toVotingPurpose :: forall (f :: * -> * -> *). PlutusPurpose f DijkstraEra -> 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 DijkstraEra _ = Maybe (f Word32 Voter) forall a. Maybe a Nothing mkProposingPurpose :: forall (f :: * -> * -> *). f Word32 (ProposalProcedure DijkstraEra) -> PlutusPurpose f DijkstraEra mkProposingPurpose = f Word32 (ProposalProcedure DijkstraEra) -> PlutusPurpose f DijkstraEra f Word32 (ProposalProcedure DijkstraEra) -> ConwayPlutusPurpose f DijkstraEra forall (f :: * -> * -> *) era. f Word32 (ProposalProcedure era) -> ConwayPlutusPurpose f era ConwayProposing toProposingPurpose :: forall (f :: * -> * -> *). PlutusPurpose f DijkstraEra -> Maybe (f Word32 (ProposalProcedure DijkstraEra)) toProposingPurpose (ConwayProposing f Word32 (ProposalProcedure DijkstraEra) i) = f Word32 (ProposalProcedure DijkstraEra) -> Maybe (f Word32 (ProposalProcedure DijkstraEra)) forall a. a -> Maybe a Just f Word32 (ProposalProcedure DijkstraEra) i toProposingPurpose PlutusPurpose f DijkstraEra _ = Maybe (f Word32 (ProposalProcedure DijkstraEra)) forall a. Maybe a Nothing instance ShelleyEraScript DijkstraEra where mkRequireSignature :: KeyHash 'Witness -> NativeScript DijkstraEra mkRequireSignature = KeyHash 'Witness -> Timelock DijkstraEra KeyHash 'Witness -> NativeScript DijkstraEra forall era. Era era => KeyHash 'Witness -> Timelock era mkRequireSignatureTimelock getRequireSignature :: NativeScript DijkstraEra -> Maybe (KeyHash 'Witness) getRequireSignature = Timelock DijkstraEra -> Maybe (KeyHash 'Witness) NativeScript DijkstraEra -> Maybe (KeyHash 'Witness) forall {k} (era :: k). Timelock era -> Maybe (KeyHash 'Witness) getRequireSignatureTimelock mkRequireAllOf :: StrictSeq (NativeScript DijkstraEra) -> NativeScript DijkstraEra mkRequireAllOf = StrictSeq (Timelock DijkstraEra) -> Timelock DijkstraEra StrictSeq (NativeScript DijkstraEra) -> NativeScript DijkstraEra forall era. Era era => StrictSeq (Timelock era) -> Timelock era mkRequireAllOfTimelock getRequireAllOf :: NativeScript DijkstraEra -> Maybe (StrictSeq (NativeScript DijkstraEra)) getRequireAllOf = Timelock DijkstraEra -> Maybe (StrictSeq (Timelock DijkstraEra)) NativeScript DijkstraEra -> Maybe (StrictSeq (NativeScript DijkstraEra)) forall {k} (era :: k). Timelock era -> Maybe (StrictSeq (Timelock era)) getRequireAllOfTimelock mkRequireAnyOf :: StrictSeq (NativeScript DijkstraEra) -> NativeScript DijkstraEra mkRequireAnyOf = StrictSeq (Timelock DijkstraEra) -> Timelock DijkstraEra StrictSeq (NativeScript DijkstraEra) -> NativeScript DijkstraEra forall era. Era era => StrictSeq (Timelock era) -> Timelock era mkRequireAnyOfTimelock getRequireAnyOf :: NativeScript DijkstraEra -> Maybe (StrictSeq (NativeScript DijkstraEra)) getRequireAnyOf = Timelock DijkstraEra -> Maybe (StrictSeq (Timelock DijkstraEra)) NativeScript DijkstraEra -> Maybe (StrictSeq (NativeScript DijkstraEra)) forall {k} (era :: k). Timelock era -> Maybe (StrictSeq (Timelock era)) getRequireAnyOfTimelock mkRequireMOf :: Int -> StrictSeq (NativeScript DijkstraEra) -> NativeScript DijkstraEra mkRequireMOf = Int -> StrictSeq (Timelock DijkstraEra) -> Timelock DijkstraEra Int -> StrictSeq (NativeScript DijkstraEra) -> NativeScript DijkstraEra forall era. Era era => Int -> StrictSeq (Timelock era) -> Timelock era mkRequireMOfTimelock getRequireMOf :: NativeScript DijkstraEra -> Maybe (Int, StrictSeq (NativeScript DijkstraEra)) getRequireMOf = Timelock DijkstraEra -> Maybe (Int, StrictSeq (Timelock DijkstraEra)) NativeScript DijkstraEra -> Maybe (Int, StrictSeq (NativeScript DijkstraEra)) forall {k} (era :: k). Timelock era -> Maybe (Int, StrictSeq (Timelock era)) getRequireMOfTimelock instance AllegraEraScript DijkstraEra where mkTimeStart :: SlotNo -> NativeScript DijkstraEra mkTimeStart = SlotNo -> Timelock DijkstraEra SlotNo -> NativeScript DijkstraEra forall era. Era era => SlotNo -> Timelock era mkTimeStartTimelock getTimeStart :: NativeScript DijkstraEra -> Maybe SlotNo getTimeStart = Timelock DijkstraEra -> Maybe SlotNo NativeScript DijkstraEra -> Maybe SlotNo forall {k} (era :: k). Timelock era -> Maybe SlotNo getTimeStartTimelock mkTimeExpire :: SlotNo -> NativeScript DijkstraEra mkTimeExpire = SlotNo -> Timelock DijkstraEra SlotNo -> NativeScript DijkstraEra forall era. Era era => SlotNo -> Timelock era mkTimeExpireTimelock getTimeExpire :: NativeScript DijkstraEra -> Maybe SlotNo getTimeExpire = Timelock DijkstraEra -> Maybe SlotNo NativeScript DijkstraEra -> Maybe SlotNo forall {k} (era :: k). Timelock era -> Maybe SlotNo getTimeExpireTimelock