module Hydra.Node.ParameterMismatch where
import Hydra.Prelude
import Hydra.Tx (Party)
import Hydra.Tx.ContestationPeriod (ContestationPeriod)
newtype ParameterMismatch = ParameterMismatch [ParamMismatch]
  deriving stock (ParameterMismatch -> ParameterMismatch -> Bool
(ParameterMismatch -> ParameterMismatch -> Bool)
-> (ParameterMismatch -> ParameterMismatch -> Bool)
-> Eq ParameterMismatch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParameterMismatch -> ParameterMismatch -> Bool
== :: ParameterMismatch -> ParameterMismatch -> Bool
$c/= :: ParameterMismatch -> ParameterMismatch -> Bool
/= :: ParameterMismatch -> ParameterMismatch -> Bool
Eq, Int -> ParameterMismatch -> ShowS
[ParameterMismatch] -> ShowS
ParameterMismatch -> String
(Int -> ParameterMismatch -> ShowS)
-> (ParameterMismatch -> String)
-> ([ParameterMismatch] -> ShowS)
-> Show ParameterMismatch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParameterMismatch -> ShowS
showsPrec :: Int -> ParameterMismatch -> ShowS
$cshow :: ParameterMismatch -> String
show :: ParameterMismatch -> String
$cshowList :: [ParameterMismatch] -> ShowS
showList :: [ParameterMismatch] -> ShowS
Show)
  deriving anyclass (Show ParameterMismatch
Typeable ParameterMismatch
(Typeable ParameterMismatch, Show ParameterMismatch) =>
(ParameterMismatch -> SomeException)
-> (SomeException -> Maybe ParameterMismatch)
-> (ParameterMismatch -> String)
-> Exception ParameterMismatch
SomeException -> Maybe ParameterMismatch
ParameterMismatch -> String
ParameterMismatch -> SomeException
forall e.
(Typeable e, Show e) =>
(e -> SomeException)
-> (SomeException -> Maybe e) -> (e -> String) -> Exception e
$ctoException :: ParameterMismatch -> SomeException
toException :: ParameterMismatch -> SomeException
$cfromException :: SomeException -> Maybe ParameterMismatch
fromException :: SomeException -> Maybe ParameterMismatch
$cdisplayException :: ParameterMismatch -> String
displayException :: ParameterMismatch -> String
Exception)
data ParamMismatch
  = ContestationPeriodMismatch {ParamMismatch -> ContestationPeriod
loadedCp :: ContestationPeriod, ParamMismatch -> ContestationPeriod
configuredCp :: ContestationPeriod}
  | PartiesMismatch {ParamMismatch -> [Party]
loadedParties :: [Party], ParamMismatch -> [Party]
configuredParties :: [Party]}
  | SavedNetworkPartiesInconsistent {ParamMismatch -> Int
numberOfParties :: Int}
  deriving stock ((forall x. ParamMismatch -> Rep ParamMismatch x)
-> (forall x. Rep ParamMismatch x -> ParamMismatch)
-> Generic ParamMismatch
forall x. Rep ParamMismatch x -> ParamMismatch
forall x. ParamMismatch -> Rep ParamMismatch x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. ParamMismatch -> Rep ParamMismatch x
from :: forall x. ParamMismatch -> Rep ParamMismatch x
$cto :: forall x. Rep ParamMismatch x -> ParamMismatch
to :: forall x. Rep ParamMismatch x -> ParamMismatch
Generic, ParamMismatch -> ParamMismatch -> Bool
(ParamMismatch -> ParamMismatch -> Bool)
-> (ParamMismatch -> ParamMismatch -> Bool) -> Eq ParamMismatch
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ParamMismatch -> ParamMismatch -> Bool
== :: ParamMismatch -> ParamMismatch -> Bool
$c/= :: ParamMismatch -> ParamMismatch -> Bool
/= :: ParamMismatch -> ParamMismatch -> Bool
Eq, Int -> ParamMismatch -> ShowS
[ParamMismatch] -> ShowS
ParamMismatch -> String
(Int -> ParamMismatch -> ShowS)
-> (ParamMismatch -> String)
-> ([ParamMismatch] -> ShowS)
-> Show ParamMismatch
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> ParamMismatch -> ShowS
showsPrec :: Int -> ParamMismatch -> ShowS
$cshow :: ParamMismatch -> String
show :: ParamMismatch -> String
$cshowList :: [ParamMismatch] -> ShowS
showList :: [ParamMismatch] -> ShowS
Show)
  deriving anyclass ([ParamMismatch] -> Value
[ParamMismatch] -> Encoding
ParamMismatch -> Bool
ParamMismatch -> Value
ParamMismatch -> Encoding
(ParamMismatch -> Value)
-> (ParamMismatch -> Encoding)
-> ([ParamMismatch] -> Value)
-> ([ParamMismatch] -> Encoding)
-> (ParamMismatch -> Bool)
-> ToJSON ParamMismatch
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: ParamMismatch -> Value
toJSON :: ParamMismatch -> Value
$ctoEncoding :: ParamMismatch -> Encoding
toEncoding :: ParamMismatch -> Encoding
$ctoJSONList :: [ParamMismatch] -> Value
toJSONList :: [ParamMismatch] -> Value
$ctoEncodingList :: [ParamMismatch] -> Encoding
toEncodingList :: [ParamMismatch] -> Encoding
$comitField :: ParamMismatch -> Bool
omitField :: ParamMismatch -> Bool
ToJSON)