{-# 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.SubGov ( DijkstraSUBGOV, DijkstraSubGovPredFailure (..), ) where import Cardano.Ledger.BaseTypes ( ShelleyBase, ) import Cardano.Ledger.Binary ( DecCBOR (..), EncCBOR (..), ) import Cardano.Ledger.Conway.Core import Cardano.Ledger.Conway.Governance import Cardano.Ledger.Conway.Rules (GovEnv, GovSignal) import Cardano.Ledger.Dijkstra.Era ( DijkstraEra, DijkstraSUBGOV, ) 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 DijkstraSubGovPredFailure era = DijkstraSubGovPredFailure deriving (Int -> DijkstraSubGovPredFailure era -> ShowS [DijkstraSubGovPredFailure era] -> ShowS DijkstraSubGovPredFailure era -> String (Int -> DijkstraSubGovPredFailure era -> ShowS) -> (DijkstraSubGovPredFailure era -> String) -> ([DijkstraSubGovPredFailure era] -> ShowS) -> Show (DijkstraSubGovPredFailure era) forall era. Int -> DijkstraSubGovPredFailure era -> ShowS forall era. [DijkstraSubGovPredFailure era] -> ShowS forall era. DijkstraSubGovPredFailure era -> String forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a $cshowsPrec :: forall era. Int -> DijkstraSubGovPredFailure era -> ShowS showsPrec :: Int -> DijkstraSubGovPredFailure era -> ShowS $cshow :: forall era. DijkstraSubGovPredFailure era -> String show :: DijkstraSubGovPredFailure era -> String $cshowList :: forall era. [DijkstraSubGovPredFailure era] -> ShowS showList :: [DijkstraSubGovPredFailure era] -> ShowS Show, DijkstraSubGovPredFailure era -> DijkstraSubGovPredFailure era -> Bool (DijkstraSubGovPredFailure era -> DijkstraSubGovPredFailure era -> Bool) -> (DijkstraSubGovPredFailure era -> DijkstraSubGovPredFailure era -> Bool) -> Eq (DijkstraSubGovPredFailure era) forall era. DijkstraSubGovPredFailure era -> DijkstraSubGovPredFailure era -> Bool forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a $c== :: forall era. DijkstraSubGovPredFailure era -> DijkstraSubGovPredFailure era -> Bool == :: DijkstraSubGovPredFailure era -> DijkstraSubGovPredFailure era -> Bool $c/= :: forall era. DijkstraSubGovPredFailure era -> DijkstraSubGovPredFailure era -> Bool /= :: DijkstraSubGovPredFailure era -> DijkstraSubGovPredFailure era -> Bool Eq, (forall x. DijkstraSubGovPredFailure era -> Rep (DijkstraSubGovPredFailure era) x) -> (forall x. Rep (DijkstraSubGovPredFailure era) x -> DijkstraSubGovPredFailure era) -> Generic (DijkstraSubGovPredFailure era) forall x. Rep (DijkstraSubGovPredFailure era) x -> DijkstraSubGovPredFailure era forall x. DijkstraSubGovPredFailure era -> Rep (DijkstraSubGovPredFailure era) x forall a. (forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a forall era x. Rep (DijkstraSubGovPredFailure era) x -> DijkstraSubGovPredFailure era forall era x. DijkstraSubGovPredFailure era -> Rep (DijkstraSubGovPredFailure era) x $cfrom :: forall era x. DijkstraSubGovPredFailure era -> Rep (DijkstraSubGovPredFailure era) x from :: forall x. DijkstraSubGovPredFailure era -> Rep (DijkstraSubGovPredFailure era) x $cto :: forall era x. Rep (DijkstraSubGovPredFailure era) x -> DijkstraSubGovPredFailure era to :: forall x. Rep (DijkstraSubGovPredFailure era) x -> DijkstraSubGovPredFailure era Generic) instance NoThunks (DijkstraSubGovPredFailure era) instance NFData (DijkstraSubGovPredFailure era) instance Era era => EncCBOR (DijkstraSubGovPredFailure era) where encCBOR :: DijkstraSubGovPredFailure era -> Encoding encCBOR DijkstraSubGovPredFailure era _ = () -> Encoding forall a. EncCBOR a => a -> Encoding encCBOR () instance Typeable era => DecCBOR (DijkstraSubGovPredFailure era) where decCBOR :: forall s. Decoder s (DijkstraSubGovPredFailure era) decCBOR = forall a s. DecCBOR a => Decoder s a decCBOR @() Decoder s () -> Decoder s (DijkstraSubGovPredFailure era) -> Decoder s (DijkstraSubGovPredFailure 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 *> DijkstraSubGovPredFailure era -> Decoder s (DijkstraSubGovPredFailure era) forall a. a -> Decoder s a forall (f :: * -> *) a. Applicative f => a -> f a pure DijkstraSubGovPredFailure era forall era. DijkstraSubGovPredFailure era DijkstraSubGovPredFailure type instance EraRuleFailure "SUBGOV" DijkstraEra = DijkstraSubGovPredFailure DijkstraEra type instance EraRuleEvent "SUBGOV" DijkstraEra = VoidEraRule "SUBGOV" DijkstraEra instance InjectRuleFailure "SUBGOV" DijkstraSubGovPredFailure DijkstraEra instance ( EraGov era , EraRule "SUBGOV" era ~ DijkstraSUBGOV era ) => STS (DijkstraSUBGOV era) where type State (DijkstraSUBGOV era) = Proposals era type Signal (DijkstraSUBGOV era) = GovSignal era type Environment (DijkstraSUBGOV era) = GovEnv era type BaseM (DijkstraSUBGOV era) = ShelleyBase type PredicateFailure (DijkstraSUBGOV era) = DijkstraSubGovPredFailure era type Event (DijkstraSUBGOV era) = Void transitionRules :: [TransitionRule (DijkstraSUBGOV era)] transitionRules = [forall era. TransitionRule (EraRule "SUBGOV" era) dijkstraSubGovTransition @era] dijkstraSubGovTransition :: TransitionRule (EraRule "SUBGOV" era) dijkstraSubGovTransition :: forall era. TransitionRule (EraRule "SUBGOV" era) dijkstraSubGovTransition = do TRC (_, st, _) <- Rule (EraRule "SUBGOV" era) 'Transition (RuleContext 'Transition (EraRule "SUBGOV" era)) F (Clause (EraRule "SUBGOV" era) 'Transition) (TRC (EraRule "SUBGOV" era)) forall sts (rtype :: RuleType). Rule sts rtype (RuleContext rtype sts) judgmentContext pure st