module Swarm.Language.Syntax.CommandMetadata where
import Data.Aeson (ToJSON)
import GHC.Generics (Generic)
data SensingType
= RobotSensing
| EntitySensing
| WorldCondition
deriving (SensingType -> SensingType -> Bool
(SensingType -> SensingType -> Bool)
-> (SensingType -> SensingType -> Bool) -> Eq SensingType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SensingType -> SensingType -> Bool
== :: SensingType -> SensingType -> Bool
$c/= :: SensingType -> SensingType -> Bool
/= :: SensingType -> SensingType -> Bool
Eq, Eq SensingType
Eq SensingType =>
(SensingType -> SensingType -> Ordering)
-> (SensingType -> SensingType -> Bool)
-> (SensingType -> SensingType -> Bool)
-> (SensingType -> SensingType -> Bool)
-> (SensingType -> SensingType -> Bool)
-> (SensingType -> SensingType -> SensingType)
-> (SensingType -> SensingType -> SensingType)
-> Ord SensingType
SensingType -> SensingType -> Bool
SensingType -> SensingType -> Ordering
SensingType -> SensingType -> SensingType
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 :: SensingType -> SensingType -> Ordering
compare :: SensingType -> SensingType -> Ordering
$c< :: SensingType -> SensingType -> Bool
< :: SensingType -> SensingType -> Bool
$c<= :: SensingType -> SensingType -> Bool
<= :: SensingType -> SensingType -> Bool
$c> :: SensingType -> SensingType -> Bool
> :: SensingType -> SensingType -> Bool
$c>= :: SensingType -> SensingType -> Bool
>= :: SensingType -> SensingType -> Bool
$cmax :: SensingType -> SensingType -> SensingType
max :: SensingType -> SensingType -> SensingType
$cmin :: SensingType -> SensingType -> SensingType
min :: SensingType -> SensingType -> SensingType
Ord, Int -> SensingType
SensingType -> Int
SensingType -> [SensingType]
SensingType -> SensingType
SensingType -> SensingType -> [SensingType]
SensingType -> SensingType -> SensingType -> [SensingType]
(SensingType -> SensingType)
-> (SensingType -> SensingType)
-> (Int -> SensingType)
-> (SensingType -> Int)
-> (SensingType -> [SensingType])
-> (SensingType -> SensingType -> [SensingType])
-> (SensingType -> SensingType -> [SensingType])
-> (SensingType -> SensingType -> SensingType -> [SensingType])
-> Enum SensingType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: SensingType -> SensingType
succ :: SensingType -> SensingType
$cpred :: SensingType -> SensingType
pred :: SensingType -> SensingType
$ctoEnum :: Int -> SensingType
toEnum :: Int -> SensingType
$cfromEnum :: SensingType -> Int
fromEnum :: SensingType -> Int
$cenumFrom :: SensingType -> [SensingType]
enumFrom :: SensingType -> [SensingType]
$cenumFromThen :: SensingType -> SensingType -> [SensingType]
enumFromThen :: SensingType -> SensingType -> [SensingType]
$cenumFromTo :: SensingType -> SensingType -> [SensingType]
enumFromTo :: SensingType -> SensingType -> [SensingType]
$cenumFromThenTo :: SensingType -> SensingType -> SensingType -> [SensingType]
enumFromThenTo :: SensingType -> SensingType -> SensingType -> [SensingType]
Enum, SensingType
SensingType -> SensingType -> Bounded SensingType
forall a. a -> a -> Bounded a
$cminBound :: SensingType
minBound :: SensingType
$cmaxBound :: SensingType
maxBound :: SensingType
Bounded, Int -> SensingType -> ShowS
[SensingType] -> ShowS
SensingType -> String
(Int -> SensingType -> ShowS)
-> (SensingType -> String)
-> ([SensingType] -> ShowS)
-> Show SensingType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> SensingType -> ShowS
showsPrec :: Int -> SensingType -> ShowS
$cshow :: SensingType -> String
show :: SensingType -> String
$cshowList :: [SensingType] -> ShowS
showList :: [SensingType] -> ShowS
Show, (forall x. SensingType -> Rep SensingType x)
-> (forall x. Rep SensingType x -> SensingType)
-> Generic SensingType
forall x. Rep SensingType x -> SensingType
forall x. SensingType -> Rep SensingType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. SensingType -> Rep SensingType x
from :: forall x. SensingType -> Rep SensingType x
$cto :: forall x. Rep SensingType x -> SensingType
to :: forall x. Rep SensingType x -> SensingType
Generic, [SensingType] -> Value
[SensingType] -> Encoding
SensingType -> Bool
SensingType -> Value
SensingType -> Encoding
(SensingType -> Value)
-> (SensingType -> Encoding)
-> ([SensingType] -> Value)
-> ([SensingType] -> Encoding)
-> (SensingType -> Bool)
-> ToJSON SensingType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: SensingType -> Value
toJSON :: SensingType -> Value
$ctoEncoding :: SensingType -> Encoding
toEncoding :: SensingType -> Encoding
$ctoJSONList :: [SensingType] -> Value
toJSONList :: [SensingType] -> Value
$ctoEncodingList :: [SensingType] -> Encoding
toEncodingList :: [SensingType] -> Encoding
$comitField :: SensingType -> Bool
omitField :: SensingType -> Bool
ToJSON)
data QueryType
=
Sensing SensingType
|
PRNG
|
APriori
deriving (QueryType -> QueryType -> Bool
(QueryType -> QueryType -> Bool)
-> (QueryType -> QueryType -> Bool) -> Eq QueryType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: QueryType -> QueryType -> Bool
== :: QueryType -> QueryType -> Bool
$c/= :: QueryType -> QueryType -> Bool
/= :: QueryType -> QueryType -> Bool
Eq, Eq QueryType
Eq QueryType =>
(QueryType -> QueryType -> Ordering)
-> (QueryType -> QueryType -> Bool)
-> (QueryType -> QueryType -> Bool)
-> (QueryType -> QueryType -> Bool)
-> (QueryType -> QueryType -> Bool)
-> (QueryType -> QueryType -> QueryType)
-> (QueryType -> QueryType -> QueryType)
-> Ord QueryType
QueryType -> QueryType -> Bool
QueryType -> QueryType -> Ordering
QueryType -> QueryType -> QueryType
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 :: QueryType -> QueryType -> Ordering
compare :: QueryType -> QueryType -> Ordering
$c< :: QueryType -> QueryType -> Bool
< :: QueryType -> QueryType -> Bool
$c<= :: QueryType -> QueryType -> Bool
<= :: QueryType -> QueryType -> Bool
$c> :: QueryType -> QueryType -> Bool
> :: QueryType -> QueryType -> Bool
$c>= :: QueryType -> QueryType -> Bool
>= :: QueryType -> QueryType -> Bool
$cmax :: QueryType -> QueryType -> QueryType
max :: QueryType -> QueryType -> QueryType
$cmin :: QueryType -> QueryType -> QueryType
min :: QueryType -> QueryType -> QueryType
Ord, Int -> QueryType -> ShowS
[QueryType] -> ShowS
QueryType -> String
(Int -> QueryType -> ShowS)
-> (QueryType -> String)
-> ([QueryType] -> ShowS)
-> Show QueryType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> QueryType -> ShowS
showsPrec :: Int -> QueryType -> ShowS
$cshow :: QueryType -> String
show :: QueryType -> String
$cshowList :: [QueryType] -> ShowS
showList :: [QueryType] -> ShowS
Show, (forall x. QueryType -> Rep QueryType x)
-> (forall x. Rep QueryType x -> QueryType) -> Generic QueryType
forall x. Rep QueryType x -> QueryType
forall x. QueryType -> Rep QueryType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. QueryType -> Rep QueryType x
from :: forall x. QueryType -> Rep QueryType x
$cto :: forall x. Rep QueryType x -> QueryType
to :: forall x. Rep QueryType x -> QueryType
Generic, [QueryType] -> Value
[QueryType] -> Encoding
QueryType -> Bool
QueryType -> Value
QueryType -> Encoding
(QueryType -> Value)
-> (QueryType -> Encoding)
-> ([QueryType] -> Value)
-> ([QueryType] -> Encoding)
-> (QueryType -> Bool)
-> ToJSON QueryType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: QueryType -> Value
toJSON :: QueryType -> Value
$ctoEncoding :: QueryType -> Encoding
toEncoding :: QueryType -> Encoding
$ctoJSONList :: [QueryType] -> Value
toJSONList :: [QueryType] -> Value
$ctoEncodingList :: [QueryType] -> Encoding
toEncodingList :: [QueryType] -> Encoding
$comitField :: QueryType -> Bool
omitField :: QueryType -> Bool
ToJSON)
data RobotChangeType
= PositionChange
| InventoryChange
| ExistenceChange
| BehaviorChange
deriving (RobotChangeType -> RobotChangeType -> Bool
(RobotChangeType -> RobotChangeType -> Bool)
-> (RobotChangeType -> RobotChangeType -> Bool)
-> Eq RobotChangeType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RobotChangeType -> RobotChangeType -> Bool
== :: RobotChangeType -> RobotChangeType -> Bool
$c/= :: RobotChangeType -> RobotChangeType -> Bool
/= :: RobotChangeType -> RobotChangeType -> Bool
Eq, Eq RobotChangeType
Eq RobotChangeType =>
(RobotChangeType -> RobotChangeType -> Ordering)
-> (RobotChangeType -> RobotChangeType -> Bool)
-> (RobotChangeType -> RobotChangeType -> Bool)
-> (RobotChangeType -> RobotChangeType -> Bool)
-> (RobotChangeType -> RobotChangeType -> Bool)
-> (RobotChangeType -> RobotChangeType -> RobotChangeType)
-> (RobotChangeType -> RobotChangeType -> RobotChangeType)
-> Ord RobotChangeType
RobotChangeType -> RobotChangeType -> Bool
RobotChangeType -> RobotChangeType -> Ordering
RobotChangeType -> RobotChangeType -> RobotChangeType
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 :: RobotChangeType -> RobotChangeType -> Ordering
compare :: RobotChangeType -> RobotChangeType -> Ordering
$c< :: RobotChangeType -> RobotChangeType -> Bool
< :: RobotChangeType -> RobotChangeType -> Bool
$c<= :: RobotChangeType -> RobotChangeType -> Bool
<= :: RobotChangeType -> RobotChangeType -> Bool
$c> :: RobotChangeType -> RobotChangeType -> Bool
> :: RobotChangeType -> RobotChangeType -> Bool
$c>= :: RobotChangeType -> RobotChangeType -> Bool
>= :: RobotChangeType -> RobotChangeType -> Bool
$cmax :: RobotChangeType -> RobotChangeType -> RobotChangeType
max :: RobotChangeType -> RobotChangeType -> RobotChangeType
$cmin :: RobotChangeType -> RobotChangeType -> RobotChangeType
min :: RobotChangeType -> RobotChangeType -> RobotChangeType
Ord, Int -> RobotChangeType
RobotChangeType -> Int
RobotChangeType -> [RobotChangeType]
RobotChangeType -> RobotChangeType
RobotChangeType -> RobotChangeType -> [RobotChangeType]
RobotChangeType
-> RobotChangeType -> RobotChangeType -> [RobotChangeType]
(RobotChangeType -> RobotChangeType)
-> (RobotChangeType -> RobotChangeType)
-> (Int -> RobotChangeType)
-> (RobotChangeType -> Int)
-> (RobotChangeType -> [RobotChangeType])
-> (RobotChangeType -> RobotChangeType -> [RobotChangeType])
-> (RobotChangeType -> RobotChangeType -> [RobotChangeType])
-> (RobotChangeType
-> RobotChangeType -> RobotChangeType -> [RobotChangeType])
-> Enum RobotChangeType
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: RobotChangeType -> RobotChangeType
succ :: RobotChangeType -> RobotChangeType
$cpred :: RobotChangeType -> RobotChangeType
pred :: RobotChangeType -> RobotChangeType
$ctoEnum :: Int -> RobotChangeType
toEnum :: Int -> RobotChangeType
$cfromEnum :: RobotChangeType -> Int
fromEnum :: RobotChangeType -> Int
$cenumFrom :: RobotChangeType -> [RobotChangeType]
enumFrom :: RobotChangeType -> [RobotChangeType]
$cenumFromThen :: RobotChangeType -> RobotChangeType -> [RobotChangeType]
enumFromThen :: RobotChangeType -> RobotChangeType -> [RobotChangeType]
$cenumFromTo :: RobotChangeType -> RobotChangeType -> [RobotChangeType]
enumFromTo :: RobotChangeType -> RobotChangeType -> [RobotChangeType]
$cenumFromThenTo :: RobotChangeType
-> RobotChangeType -> RobotChangeType -> [RobotChangeType]
enumFromThenTo :: RobotChangeType
-> RobotChangeType -> RobotChangeType -> [RobotChangeType]
Enum, RobotChangeType
RobotChangeType -> RobotChangeType -> Bounded RobotChangeType
forall a. a -> a -> Bounded a
$cminBound :: RobotChangeType
minBound :: RobotChangeType
$cmaxBound :: RobotChangeType
maxBound :: RobotChangeType
Bounded, Int -> RobotChangeType -> ShowS
[RobotChangeType] -> ShowS
RobotChangeType -> String
(Int -> RobotChangeType -> ShowS)
-> (RobotChangeType -> String)
-> ([RobotChangeType] -> ShowS)
-> Show RobotChangeType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> RobotChangeType -> ShowS
showsPrec :: Int -> RobotChangeType -> ShowS
$cshow :: RobotChangeType -> String
show :: RobotChangeType -> String
$cshowList :: [RobotChangeType] -> ShowS
showList :: [RobotChangeType] -> ShowS
Show, (forall x. RobotChangeType -> Rep RobotChangeType x)
-> (forall x. Rep RobotChangeType x -> RobotChangeType)
-> Generic RobotChangeType
forall x. Rep RobotChangeType x -> RobotChangeType
forall x. RobotChangeType -> Rep RobotChangeType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. RobotChangeType -> Rep RobotChangeType x
from :: forall x. RobotChangeType -> Rep RobotChangeType x
$cto :: forall x. Rep RobotChangeType x -> RobotChangeType
to :: forall x. Rep RobotChangeType x -> RobotChangeType
Generic, [RobotChangeType] -> Value
[RobotChangeType] -> Encoding
RobotChangeType -> Bool
RobotChangeType -> Value
RobotChangeType -> Encoding
(RobotChangeType -> Value)
-> (RobotChangeType -> Encoding)
-> ([RobotChangeType] -> Value)
-> ([RobotChangeType] -> Encoding)
-> (RobotChangeType -> Bool)
-> ToJSON RobotChangeType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: RobotChangeType -> Value
toJSON :: RobotChangeType -> Value
$ctoEncoding :: RobotChangeType -> Encoding
toEncoding :: RobotChangeType -> Encoding
$ctoJSONList :: [RobotChangeType] -> Value
toJSONList :: [RobotChangeType] -> Value
$ctoEncodingList :: [RobotChangeType] -> Encoding
toEncodingList :: [RobotChangeType] -> Encoding
$comitField :: RobotChangeType -> Bool
omitField :: RobotChangeType -> Bool
ToJSON)
data MutationType
= Cosmetic
| LogEmission
| EntityChange
| RobotChange RobotChangeType
deriving (MutationType -> MutationType -> Bool
(MutationType -> MutationType -> Bool)
-> (MutationType -> MutationType -> Bool) -> Eq MutationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: MutationType -> MutationType -> Bool
== :: MutationType -> MutationType -> Bool
$c/= :: MutationType -> MutationType -> Bool
/= :: MutationType -> MutationType -> Bool
Eq, Eq MutationType
Eq MutationType =>
(MutationType -> MutationType -> Ordering)
-> (MutationType -> MutationType -> Bool)
-> (MutationType -> MutationType -> Bool)
-> (MutationType -> MutationType -> Bool)
-> (MutationType -> MutationType -> Bool)
-> (MutationType -> MutationType -> MutationType)
-> (MutationType -> MutationType -> MutationType)
-> Ord MutationType
MutationType -> MutationType -> Bool
MutationType -> MutationType -> Ordering
MutationType -> MutationType -> MutationType
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 :: MutationType -> MutationType -> Ordering
compare :: MutationType -> MutationType -> Ordering
$c< :: MutationType -> MutationType -> Bool
< :: MutationType -> MutationType -> Bool
$c<= :: MutationType -> MutationType -> Bool
<= :: MutationType -> MutationType -> Bool
$c> :: MutationType -> MutationType -> Bool
> :: MutationType -> MutationType -> Bool
$c>= :: MutationType -> MutationType -> Bool
>= :: MutationType -> MutationType -> Bool
$cmax :: MutationType -> MutationType -> MutationType
max :: MutationType -> MutationType -> MutationType
$cmin :: MutationType -> MutationType -> MutationType
min :: MutationType -> MutationType -> MutationType
Ord, Int -> MutationType -> ShowS
[MutationType] -> ShowS
MutationType -> String
(Int -> MutationType -> ShowS)
-> (MutationType -> String)
-> ([MutationType] -> ShowS)
-> Show MutationType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> MutationType -> ShowS
showsPrec :: Int -> MutationType -> ShowS
$cshow :: MutationType -> String
show :: MutationType -> String
$cshowList :: [MutationType] -> ShowS
showList :: [MutationType] -> ShowS
Show, (forall x. MutationType -> Rep MutationType x)
-> (forall x. Rep MutationType x -> MutationType)
-> Generic MutationType
forall x. Rep MutationType x -> MutationType
forall x. MutationType -> Rep MutationType x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. MutationType -> Rep MutationType x
from :: forall x. MutationType -> Rep MutationType x
$cto :: forall x. Rep MutationType x -> MutationType
to :: forall x. Rep MutationType x -> MutationType
Generic, [MutationType] -> Value
[MutationType] -> Encoding
MutationType -> Bool
MutationType -> Value
MutationType -> Encoding
(MutationType -> Value)
-> (MutationType -> Encoding)
-> ([MutationType] -> Value)
-> ([MutationType] -> Encoding)
-> (MutationType -> Bool)
-> ToJSON MutationType
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: MutationType -> Value
toJSON :: MutationType -> Value
$ctoEncoding :: MutationType -> Encoding
toEncoding :: MutationType -> Encoding
$ctoJSONList :: [MutationType] -> Value
toJSONList :: [MutationType] -> Value
$ctoEncodingList :: [MutationType] -> Encoding
toEncodingList :: [MutationType] -> Encoding
$comitField :: MutationType -> Bool
omitField :: MutationType -> Bool
ToJSON)
data CommandEffect
= Query QueryType
| MetaEffect
| Mutation MutationType
deriving (CommandEffect -> CommandEffect -> Bool
(CommandEffect -> CommandEffect -> Bool)
-> (CommandEffect -> CommandEffect -> Bool) -> Eq CommandEffect
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: CommandEffect -> CommandEffect -> Bool
== :: CommandEffect -> CommandEffect -> Bool
$c/= :: CommandEffect -> CommandEffect -> Bool
/= :: CommandEffect -> CommandEffect -> Bool
Eq, Eq CommandEffect
Eq CommandEffect =>
(CommandEffect -> CommandEffect -> Ordering)
-> (CommandEffect -> CommandEffect -> Bool)
-> (CommandEffect -> CommandEffect -> Bool)
-> (CommandEffect -> CommandEffect -> Bool)
-> (CommandEffect -> CommandEffect -> Bool)
-> (CommandEffect -> CommandEffect -> CommandEffect)
-> (CommandEffect -> CommandEffect -> CommandEffect)
-> Ord CommandEffect
CommandEffect -> CommandEffect -> Bool
CommandEffect -> CommandEffect -> Ordering
CommandEffect -> CommandEffect -> CommandEffect
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 :: CommandEffect -> CommandEffect -> Ordering
compare :: CommandEffect -> CommandEffect -> Ordering
$c< :: CommandEffect -> CommandEffect -> Bool
< :: CommandEffect -> CommandEffect -> Bool
$c<= :: CommandEffect -> CommandEffect -> Bool
<= :: CommandEffect -> CommandEffect -> Bool
$c> :: CommandEffect -> CommandEffect -> Bool
> :: CommandEffect -> CommandEffect -> Bool
$c>= :: CommandEffect -> CommandEffect -> Bool
>= :: CommandEffect -> CommandEffect -> Bool
$cmax :: CommandEffect -> CommandEffect -> CommandEffect
max :: CommandEffect -> CommandEffect -> CommandEffect
$cmin :: CommandEffect -> CommandEffect -> CommandEffect
min :: CommandEffect -> CommandEffect -> CommandEffect
Ord, Int -> CommandEffect -> ShowS
[CommandEffect] -> ShowS
CommandEffect -> String
(Int -> CommandEffect -> ShowS)
-> (CommandEffect -> String)
-> ([CommandEffect] -> ShowS)
-> Show CommandEffect
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> CommandEffect -> ShowS
showsPrec :: Int -> CommandEffect -> ShowS
$cshow :: CommandEffect -> String
show :: CommandEffect -> String
$cshowList :: [CommandEffect] -> ShowS
showList :: [CommandEffect] -> ShowS
Show, (forall x. CommandEffect -> Rep CommandEffect x)
-> (forall x. Rep CommandEffect x -> CommandEffect)
-> Generic CommandEffect
forall x. Rep CommandEffect x -> CommandEffect
forall x. CommandEffect -> Rep CommandEffect x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cfrom :: forall x. CommandEffect -> Rep CommandEffect x
from :: forall x. CommandEffect -> Rep CommandEffect x
$cto :: forall x. Rep CommandEffect x -> CommandEffect
to :: forall x. Rep CommandEffect x -> CommandEffect
Generic, [CommandEffect] -> Value
[CommandEffect] -> Encoding
CommandEffect -> Bool
CommandEffect -> Value
CommandEffect -> Encoding
(CommandEffect -> Value)
-> (CommandEffect -> Encoding)
-> ([CommandEffect] -> Value)
-> ([CommandEffect] -> Encoding)
-> (CommandEffect -> Bool)
-> ToJSON CommandEffect
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> (a -> Bool)
-> ToJSON a
$ctoJSON :: CommandEffect -> Value
toJSON :: CommandEffect -> Value
$ctoEncoding :: CommandEffect -> Encoding
toEncoding :: CommandEffect -> Encoding
$ctoJSONList :: [CommandEffect] -> Value
toJSONList :: [CommandEffect] -> Value
$ctoEncodingList :: [CommandEffect] -> Encoding
toEncodingList :: [CommandEffect] -> Encoding
$comitField :: CommandEffect -> Bool
omitField :: CommandEffect -> Bool
ToJSON)