{-# LANGUAGE Safe #-}
module Language.GraphQL.AST.DirectiveLocation
( DirectiveLocation(..)
, ExecutableDirectiveLocation(..)
, TypeSystemDirectiveLocation(..)
) where
data DirectiveLocation
= ExecutableDirectiveLocation ExecutableDirectiveLocation
| TypeSystemDirectiveLocation TypeSystemDirectiveLocation
deriving DirectiveLocation -> DirectiveLocation -> Bool
(DirectiveLocation -> DirectiveLocation -> Bool)
-> (DirectiveLocation -> DirectiveLocation -> Bool)
-> Eq DirectiveLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DirectiveLocation -> DirectiveLocation -> Bool
$c/= :: DirectiveLocation -> DirectiveLocation -> Bool
== :: DirectiveLocation -> DirectiveLocation -> Bool
$c== :: DirectiveLocation -> DirectiveLocation -> Bool
Eq
instance Show DirectiveLocation where
show :: DirectiveLocation -> String
show (ExecutableDirectiveLocation ExecutableDirectiveLocation
directiveLocation) =
ExecutableDirectiveLocation -> String
forall a. Show a => a -> String
show ExecutableDirectiveLocation
directiveLocation
show (TypeSystemDirectiveLocation TypeSystemDirectiveLocation
directiveLocation) =
TypeSystemDirectiveLocation -> String
forall a. Show a => a -> String
show TypeSystemDirectiveLocation
directiveLocation
data ExecutableDirectiveLocation
= Query
| Mutation
| Subscription
| Field
| FragmentDefinition
| FragmentSpread
| InlineFragment
deriving ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
(ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Bool)
-> (ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Bool)
-> Eq ExecutableDirectiveLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
$c/= :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
== :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
$c== :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
Eq
instance Show ExecutableDirectiveLocation where
show :: ExecutableDirectiveLocation -> String
show ExecutableDirectiveLocation
Query = String
"QUERY"
show ExecutableDirectiveLocation
Mutation = String
"MUTATION"
show ExecutableDirectiveLocation
Subscription = String
"SUBSCRIPTION"
show ExecutableDirectiveLocation
Field = String
"FIELD"
show ExecutableDirectiveLocation
FragmentDefinition = String
"FRAGMENT_DEFINITION"
show ExecutableDirectiveLocation
FragmentSpread = String
"FRAGMENT_SPREAD"
show ExecutableDirectiveLocation
InlineFragment = String
"INLINE_FRAGMENT"
data TypeSystemDirectiveLocation
= Schema
| Scalar
| Object
| FieldDefinition
| ArgumentDefinition
| Interface
| Union
| Enum
| EnumValue
| InputObject
| InputFieldDefinition
deriving TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
(TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Bool)
-> (TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Bool)
-> Eq TypeSystemDirectiveLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
$c/= :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
== :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
$c== :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
Eq
instance Show TypeSystemDirectiveLocation where
show :: TypeSystemDirectiveLocation -> String
show TypeSystemDirectiveLocation
Schema = String
"SCHEMA"
show TypeSystemDirectiveLocation
Scalar = String
"SCALAR"
show TypeSystemDirectiveLocation
Object = String
"OBJECT"
show TypeSystemDirectiveLocation
FieldDefinition = String
"FIELD_DEFINITION"
show TypeSystemDirectiveLocation
ArgumentDefinition = String
"ARGUMENT_DEFINITION"
show TypeSystemDirectiveLocation
Interface = String
"INTERFACE"
show TypeSystemDirectiveLocation
Union = String
"UNION"
show TypeSystemDirectiveLocation
Enum = String
"ENUM"
show TypeSystemDirectiveLocation
EnumValue = String
"ENUM_VALUE"
show TypeSystemDirectiveLocation
InputObject = String
"INPUT_OBJECT"
show TypeSystemDirectiveLocation
InputFieldDefinition = String
"INPUT_FIELD_DEFINITION"