{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE EmptyDataDeriving #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE GeneralisedNewtypeDeriving #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} {-# OPTIONS_GHC -Wno-orphans #-} module Cardano.Ledger.Dijkstra.Rules.SubGovCert ( DijkstraSUBGOVCERT, DijkstraSubGovCertPredFailure (..), ) where import Cardano.Ledger.BaseTypes ( ShelleyBase, ) import Cardano.Ledger.Binary ( DecCBOR (..), EncCBOR (..), ) import Cardano.Ledger.Conway.Core import Cardano.Ledger.Conway.Rules (ConwayGovCertEnv) import Cardano.Ledger.Conway.State import Cardano.Ledger.Conway.TxCert (ConwayGovCert) import Cardano.Ledger.Dijkstra.Era ( DijkstraEra, DijkstraSUBGOVCERT, ) import Cardano.Ledger.Dijkstra.Rules.GovCert (DijkstraGovCertPredFailure) import Control.DeepSeq (NFData) import Control.State.Transition.Extended ( BaseM, Environment, Event, PredicateFailure, STS, Signal, State, TRC (TRC), TransitionRule, judgmentContext, transitionRules, ) import Data.Void (Void) import GHC.Generics (Generic) import NoThunks.Class (NoThunks (..)) newtype DijkstraSubGovCertPredFailure era = DijkstraSubGovCertPredFailure (DijkstraGovCertPredFailure era) deriving (Int -> DijkstraSubGovCertPredFailure era -> ShowS [DijkstraSubGovCertPredFailure era] -> ShowS DijkstraSubGovCertPredFailure era -> String (Int -> DijkstraSubGovCertPredFailure era -> ShowS) -> (DijkstraSubGovCertPredFailure era -> String) -> ([DijkstraSubGovCertPredFailure era] -> ShowS) -> Show (DijkstraSubGovCertPredFailure era) forall era. Int -> DijkstraSubGovCertPredFailure era -> ShowS forall era. [DijkstraSubGovCertPredFailure era] -> ShowS forall era. DijkstraSubGovCertPredFailure era -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: forall era. Int -> DijkstraSubGovCertPredFailure era -> ShowS showsPrec :: Int -> DijkstraSubGovCertPredFailure era -> ShowS $cshow :: forall era. DijkstraSubGovCertPredFailure era -> String show :: DijkstraSubGovCertPredFailure era -> String $cshowList :: forall era. [DijkstraSubGovCertPredFailure era] -> ShowS showList :: [DijkstraSubGovCertPredFailure era] -> ShowS Show, DijkstraSubGovCertPredFailure era -> DijkstraSubGovCertPredFailure era -> Bool (DijkstraSubGovCertPredFailure era -> DijkstraSubGovCertPredFailure era -> Bool) -> (DijkstraSubGovCertPredFailure era -> DijkstraSubGovCertPredFailure era -> Bool) -> Eq (DijkstraSubGovCertPredFailure era) forall era. DijkstraSubGovCertPredFailure era -> DijkstraSubGovCertPredFailure era -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: forall era. DijkstraSubGovCertPredFailure era -> DijkstraSubGovCertPredFailure era -> Bool == :: DijkstraSubGovCertPredFailure era -> DijkstraSubGovCertPredFailure era -> Bool $c/= :: forall era. DijkstraSubGovCertPredFailure era -> DijkstraSubGovCertPredFailure era -> Bool /= :: DijkstraSubGovCertPredFailure era -> DijkstraSubGovCertPredFailure era -> Bool Eq, (forall x. DijkstraSubGovCertPredFailure era -> Rep (DijkstraSubGovCertPredFailure era) x) -> (forall x. Rep (DijkstraSubGovCertPredFailure era) x -> DijkstraSubGovCertPredFailure era) -> Generic (DijkstraSubGovCertPredFailure era) forall x. Rep (DijkstraSubGovCertPredFailure era) x -> DijkstraSubGovCertPredFailure era forall x. DijkstraSubGovCertPredFailure era -> Rep (DijkstraSubGovCertPredFailure era) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall era x. Rep (DijkstraSubGovCertPredFailure era) x -> DijkstraSubGovCertPredFailure era forall era x. DijkstraSubGovCertPredFailure era -> Rep (DijkstraSubGovCertPredFailure era) x $cfrom :: forall era x. DijkstraSubGovCertPredFailure era -> Rep (DijkstraSubGovCertPredFailure era) x from :: forall x. DijkstraSubGovCertPredFailure era -> Rep (DijkstraSubGovCertPredFailure era) x $cto :: forall era x. Rep (DijkstraSubGovCertPredFailure era) x -> DijkstraSubGovCertPredFailure era to :: forall x. Rep (DijkstraSubGovCertPredFailure era) x -> DijkstraSubGovCertPredFailure era Generic, DijkstraSubGovCertPredFailure era -> () (DijkstraSubGovCertPredFailure era -> ()) -> NFData (DijkstraSubGovCertPredFailure era) forall era. DijkstraSubGovCertPredFailure era -> () forall a. (a -> ()) -> NFData a $crnf :: forall era. DijkstraSubGovCertPredFailure era -> () rnf :: DijkstraSubGovCertPredFailure era -> () NFData, Context -> DijkstraSubGovCertPredFailure era -> IO (Maybe ThunkInfo) Proxy (DijkstraSubGovCertPredFailure era) -> String (Context -> DijkstraSubGovCertPredFailure era -> IO (Maybe ThunkInfo)) -> (Context -> DijkstraSubGovCertPredFailure era -> IO (Maybe ThunkInfo)) -> (Proxy (DijkstraSubGovCertPredFailure era) -> String) -> NoThunks (DijkstraSubGovCertPredFailure era) forall era. Context -> DijkstraSubGovCertPredFailure era -> IO (Maybe ThunkInfo) forall era. Proxy (DijkstraSubGovCertPredFailure era) -> String forall a. (Context -> a -> IO (Maybe ThunkInfo)) -> (Context -> a -> IO (Maybe ThunkInfo)) -> (Proxy a -> String) -> NoThunks a $cnoThunks :: forall era. Context -> DijkstraSubGovCertPredFailure era -> IO (Maybe ThunkInfo) noThunks :: Context -> DijkstraSubGovCertPredFailure era -> IO (Maybe ThunkInfo) $cwNoThunks :: forall era. Context -> DijkstraSubGovCertPredFailure era -> IO (Maybe ThunkInfo) wNoThunks :: Context -> DijkstraSubGovCertPredFailure era -> IO (Maybe ThunkInfo) $cshowTypeOf :: forall era. Proxy (DijkstraSubGovCertPredFailure era) -> String showTypeOf :: Proxy (DijkstraSubGovCertPredFailure era) -> String NoThunks, DijkstraSubGovCertPredFailure era -> Encoding (DijkstraSubGovCertPredFailure era -> Encoding) -> EncCBOR (DijkstraSubGovCertPredFailure era) forall era. Era era => DijkstraSubGovCertPredFailure era -> Encoding forall a. (a -> Encoding) -> EncCBOR a $cencCBOR :: forall era. Era era => DijkstraSubGovCertPredFailure era -> Encoding encCBOR :: DijkstraSubGovCertPredFailure era -> Encoding EncCBOR, Typeable (DijkstraSubGovCertPredFailure era) Typeable (DijkstraSubGovCertPredFailure era) => (forall s. Decoder s (DijkstraSubGovCertPredFailure era)) -> (forall s. Proxy (DijkstraSubGovCertPredFailure era) -> Decoder s ()) -> (Proxy (DijkstraSubGovCertPredFailure era) -> Text) -> DecCBOR (DijkstraSubGovCertPredFailure era) Proxy (DijkstraSubGovCertPredFailure era) -> Text forall s. Decoder s (DijkstraSubGovCertPredFailure era) forall era. Typeable era => Typeable (DijkstraSubGovCertPredFailure era) forall era. Typeable era => Proxy (DijkstraSubGovCertPredFailure era) -> Text forall a. Typeable a => (forall s. Decoder s a) -> (forall s. Proxy a -> Decoder s ()) -> (Proxy a -> Text) -> DecCBOR a forall era s. Typeable era => Decoder s (DijkstraSubGovCertPredFailure era) forall era s. Typeable era => Proxy (DijkstraSubGovCertPredFailure era) -> Decoder s () forall s. Proxy (DijkstraSubGovCertPredFailure era) -> Decoder s () $cdecCBOR :: forall era s. Typeable era => Decoder s (DijkstraSubGovCertPredFailure era) decCBOR :: forall s. Decoder s (DijkstraSubGovCertPredFailure era) $cdropCBOR :: forall era s. Typeable era => Proxy (DijkstraSubGovCertPredFailure era) -> Decoder s () dropCBOR :: forall s. Proxy (DijkstraSubGovCertPredFailure era) -> Decoder s () $clabel :: forall era. Typeable era => Proxy (DijkstraSubGovCertPredFailure era) -> Text label :: Proxy (DijkstraSubGovCertPredFailure era) -> Text DecCBOR) type instance EraRuleFailure "SUBGOVCERT" DijkstraEra = DijkstraSubGovCertPredFailure DijkstraEra type instance EraRuleEvent "SUBGOVCERT" DijkstraEra = VoidEraRule "SUBGOVCERT" DijkstraEra instance InjectRuleFailure "SUBGOVCERT" DijkstraSubGovCertPredFailure DijkstraEra instance ( EraGov era , EraCertState era , EraRule "SUBGOVCERT" era ~ DijkstraSUBGOVCERT era ) => STS (DijkstraSUBGOVCERT era) where type State (DijkstraSUBGOVCERT era) = CertState era type Signal (DijkstraSUBGOVCERT era) = ConwayGovCert type Environment (DijkstraSUBGOVCERT era) = ConwayGovCertEnv era type BaseM (DijkstraSUBGOVCERT era) = ShelleyBase type PredicateFailure (DijkstraSUBGOVCERT era) = DijkstraSubGovCertPredFailure era type Event (DijkstraSUBGOVCERT era) = Void transitionRules :: [TransitionRule (DijkstraSUBGOVCERT era)] transitionRules = [forall era. TransitionRule (EraRule "SUBGOVCERT" era) dijkstraSubGovCertTransition @era] dijkstraSubGovCertTransition :: TransitionRule (EraRule "SUBGOVCERT" era) dijkstraSubGovCertTransition :: forall era. TransitionRule (EraRule "SUBGOVCERT" era) dijkstraSubGovCertTransition = do TRC (_, st, _) <- Rule (EraRule "SUBGOVCERT" era) 'Transition (RuleContext 'Transition (EraRule "SUBGOVCERT" era)) F (Clause (EraRule "SUBGOVCERT" era) 'Transition) (TRC (EraRule "SUBGOVCERT" era)) forall sts (rtype :: RuleType). Rule sts rtype (RuleContext rtype sts) judgmentContext pure st