{-# 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 directiveLocation :: ExecutableDirectiveLocation
directiveLocation) =
ExecutableDirectiveLocation -> String
forall a. Show a => a -> String
show ExecutableDirectiveLocation
directiveLocation
show (TypeSystemDirectiveLocation directiveLocation :: 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 Query = "QUERY"
show Mutation = "MUTATION"
show Subscription = "SUBSCRIPTION"
show Field = "FIELD"
show FragmentDefinition = "FRAGMENT_DEFINITION"
show FragmentSpread = "FRAGMENT_SPREAD"
show InlineFragment = "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 Schema = "SCHEMA"
show Scalar = "SCALAR"
show Object = "OBJECT"
show FieldDefinition = "FIELD_DEFINITION"
show ArgumentDefinition = "ARGUMENT_DEFINITION"
show Interface = "INTERFACE"
show Union = "UNION"
show Enum = "ENUM"
show EnumValue = "ENUM_VALUE"
show InputObject = "INPUT_OBJECT"
show InputFieldDefinition = "INPUT_FIELD_DEFINITION"