{-# LANGUAGE AllowAmbiguousTypes #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE EmptyDataDeriving #-} {-# LANGUAGE FlexibleContexts #-} {-# 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 Control.DeepSeq (NFData) import Control.State.Transition.Extended ( BaseM, Environment, Event, PredicateFailure, STS, Signal, State, TRC (TRC), TransitionRule, judgmentContext, transitionRules, ) import Data.Typeable (Typeable) import Data.Void (Void) import GHC.Generics (Generic) import NoThunks.Class (NoThunks (..)) data DijkstraSubGovCertPredFailure era = DijkstraSubGovCertPredFailure 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) instance NoThunks (DijkstraSubGovCertPredFailure era) instance NFData (DijkstraSubGovCertPredFailure era) instance Era era => EncCBOR (DijkstraSubGovCertPredFailure era) where encCBOR :: DijkstraSubGovCertPredFailure era -> Encoding encCBOR DijkstraSubGovCertPredFailure era _ = () -> Encoding forall a. EncCBOR a => a -> Encoding encCBOR () instance Typeable era => DecCBOR (DijkstraSubGovCertPredFailure era) where decCBOR :: forall s. Decoder s (DijkstraSubGovCertPredFailure era) decCBOR = forall a s. DecCBOR a => Decoder s a decCBOR @() Decoder s () -> Decoder s (DijkstraSubGovCertPredFailure era) -> Decoder s (DijkstraSubGovCertPredFailure era) forall a b. Decoder s a -> Decoder s b -> Decoder s b forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> DijkstraSubGovCertPredFailure era -> Decoder s (DijkstraSubGovCertPredFailure era) forall a. a -> Decoder s a forall (f :: * -> *) a. Applicative f => a -> f a pure DijkstraSubGovCertPredFailure era forall era. DijkstraSubGovCertPredFailure era DijkstraSubGovCertPredFailure 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