-- | A GraphQL model. Based on the (extended) BNF at:
-- |   https://spec.graphql.org/draft/#sec-Appendix-Grammar-Summary

module Hydra.Ext.Graphql.Syntax where

import qualified Hydra.Core as Core
import Data.List
import Data.Map
import Data.Set

newtype Name = 
  Name {
    Name -> String
unName :: String}
  deriving (Name -> Name -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Name -> Name -> Bool
$c/= :: Name -> Name -> Bool
== :: Name -> Name -> Bool
$c== :: Name -> Name -> Bool
Eq, Eq Name
Name -> Name -> Bool
Name -> Name -> Ordering
Name -> Name -> Name
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
min :: Name -> Name -> Name
$cmin :: Name -> Name -> Name
max :: Name -> Name -> Name
$cmax :: Name -> Name -> Name
>= :: Name -> Name -> Bool
$c>= :: Name -> Name -> Bool
> :: Name -> Name -> Bool
$c> :: Name -> Name -> Bool
<= :: Name -> Name -> Bool
$c<= :: Name -> Name -> Bool
< :: Name -> Name -> Bool
$c< :: Name -> Name -> Bool
compare :: Name -> Name -> Ordering
$ccompare :: Name -> Name -> Ordering
Ord, ReadPrec [Name]
ReadPrec Name
Int -> ReadS Name
ReadS [Name]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Name]
$creadListPrec :: ReadPrec [Name]
readPrec :: ReadPrec Name
$creadPrec :: ReadPrec Name
readList :: ReadS [Name]
$creadList :: ReadS [Name]
readsPrec :: Int -> ReadS Name
$creadsPrec :: Int -> ReadS Name
Read, Int -> Name -> String -> String
[Name] -> String -> String
Name -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Name] -> String -> String
$cshowList :: [Name] -> String -> String
show :: Name -> String
$cshow :: Name -> String
showsPrec :: Int -> Name -> String -> String
$cshowsPrec :: Int -> Name -> String -> String
Show)

_Name :: Name
_Name = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Name")

newtype IntValue = 
  IntValue {
    IntValue -> String
unIntValue :: String}
  deriving (IntValue -> IntValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: IntValue -> IntValue -> Bool
$c/= :: IntValue -> IntValue -> Bool
== :: IntValue -> IntValue -> Bool
$c== :: IntValue -> IntValue -> Bool
Eq, Eq IntValue
IntValue -> IntValue -> Bool
IntValue -> IntValue -> Ordering
IntValue -> IntValue -> IntValue
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
min :: IntValue -> IntValue -> IntValue
$cmin :: IntValue -> IntValue -> IntValue
max :: IntValue -> IntValue -> IntValue
$cmax :: IntValue -> IntValue -> IntValue
>= :: IntValue -> IntValue -> Bool
$c>= :: IntValue -> IntValue -> Bool
> :: IntValue -> IntValue -> Bool
$c> :: IntValue -> IntValue -> Bool
<= :: IntValue -> IntValue -> Bool
$c<= :: IntValue -> IntValue -> Bool
< :: IntValue -> IntValue -> Bool
$c< :: IntValue -> IntValue -> Bool
compare :: IntValue -> IntValue -> Ordering
$ccompare :: IntValue -> IntValue -> Ordering
Ord, ReadPrec [IntValue]
ReadPrec IntValue
Int -> ReadS IntValue
ReadS [IntValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [IntValue]
$creadListPrec :: ReadPrec [IntValue]
readPrec :: ReadPrec IntValue
$creadPrec :: ReadPrec IntValue
readList :: ReadS [IntValue]
$creadList :: ReadS [IntValue]
readsPrec :: Int -> ReadS IntValue
$creadsPrec :: Int -> ReadS IntValue
Read, Int -> IntValue -> String -> String
[IntValue] -> String -> String
IntValue -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [IntValue] -> String -> String
$cshowList :: [IntValue] -> String -> String
show :: IntValue -> String
$cshow :: IntValue -> String
showsPrec :: Int -> IntValue -> String -> String
$cshowsPrec :: Int -> IntValue -> String -> String
Show)

_IntValue :: Name
_IntValue = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.IntValue")

newtype FloatValue = 
  FloatValue {
    FloatValue -> String
unFloatValue :: String}
  deriving (FloatValue -> FloatValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FloatValue -> FloatValue -> Bool
$c/= :: FloatValue -> FloatValue -> Bool
== :: FloatValue -> FloatValue -> Bool
$c== :: FloatValue -> FloatValue -> Bool
Eq, Eq FloatValue
FloatValue -> FloatValue -> Bool
FloatValue -> FloatValue -> Ordering
FloatValue -> FloatValue -> FloatValue
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
min :: FloatValue -> FloatValue -> FloatValue
$cmin :: FloatValue -> FloatValue -> FloatValue
max :: FloatValue -> FloatValue -> FloatValue
$cmax :: FloatValue -> FloatValue -> FloatValue
>= :: FloatValue -> FloatValue -> Bool
$c>= :: FloatValue -> FloatValue -> Bool
> :: FloatValue -> FloatValue -> Bool
$c> :: FloatValue -> FloatValue -> Bool
<= :: FloatValue -> FloatValue -> Bool
$c<= :: FloatValue -> FloatValue -> Bool
< :: FloatValue -> FloatValue -> Bool
$c< :: FloatValue -> FloatValue -> Bool
compare :: FloatValue -> FloatValue -> Ordering
$ccompare :: FloatValue -> FloatValue -> Ordering
Ord, ReadPrec [FloatValue]
ReadPrec FloatValue
Int -> ReadS FloatValue
ReadS [FloatValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FloatValue]
$creadListPrec :: ReadPrec [FloatValue]
readPrec :: ReadPrec FloatValue
$creadPrec :: ReadPrec FloatValue
readList :: ReadS [FloatValue]
$creadList :: ReadS [FloatValue]
readsPrec :: Int -> ReadS FloatValue
$creadsPrec :: Int -> ReadS FloatValue
Read, Int -> FloatValue -> String -> String
[FloatValue] -> String -> String
FloatValue -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FloatValue] -> String -> String
$cshowList :: [FloatValue] -> String -> String
show :: FloatValue -> String
$cshow :: FloatValue -> String
showsPrec :: Int -> FloatValue -> String -> String
$cshowsPrec :: Int -> FloatValue -> String -> String
Show)

_FloatValue :: Name
_FloatValue = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.FloatValue")

newtype StringValue = 
  StringValue {
    StringValue -> String
unStringValue :: String}
  deriving (StringValue -> StringValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: StringValue -> StringValue -> Bool
$c/= :: StringValue -> StringValue -> Bool
== :: StringValue -> StringValue -> Bool
$c== :: StringValue -> StringValue -> Bool
Eq, Eq StringValue
StringValue -> StringValue -> Bool
StringValue -> StringValue -> Ordering
StringValue -> StringValue -> StringValue
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
min :: StringValue -> StringValue -> StringValue
$cmin :: StringValue -> StringValue -> StringValue
max :: StringValue -> StringValue -> StringValue
$cmax :: StringValue -> StringValue -> StringValue
>= :: StringValue -> StringValue -> Bool
$c>= :: StringValue -> StringValue -> Bool
> :: StringValue -> StringValue -> Bool
$c> :: StringValue -> StringValue -> Bool
<= :: StringValue -> StringValue -> Bool
$c<= :: StringValue -> StringValue -> Bool
< :: StringValue -> StringValue -> Bool
$c< :: StringValue -> StringValue -> Bool
compare :: StringValue -> StringValue -> Ordering
$ccompare :: StringValue -> StringValue -> Ordering
Ord, ReadPrec [StringValue]
ReadPrec StringValue
Int -> ReadS StringValue
ReadS [StringValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [StringValue]
$creadListPrec :: ReadPrec [StringValue]
readPrec :: ReadPrec StringValue
$creadPrec :: ReadPrec StringValue
readList :: ReadS [StringValue]
$creadList :: ReadS [StringValue]
readsPrec :: Int -> ReadS StringValue
$creadsPrec :: Int -> ReadS StringValue
Read, Int -> StringValue -> String -> String
[StringValue] -> String -> String
StringValue -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [StringValue] -> String -> String
$cshowList :: [StringValue] -> String -> String
show :: StringValue -> String
$cshow :: StringValue -> String
showsPrec :: Int -> StringValue -> String -> String
$cshowsPrec :: Int -> StringValue -> String -> String
Show)

_StringValue :: Name
_StringValue = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.StringValue")

newtype Document = 
  Document {
    Document -> [Definition]
unDocument :: [Definition]}
  deriving (Document -> Document -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Document -> Document -> Bool
$c/= :: Document -> Document -> Bool
== :: Document -> Document -> Bool
$c== :: Document -> Document -> Bool
Eq, Eq Document
Document -> Document -> Bool
Document -> Document -> Ordering
Document -> Document -> Document
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
min :: Document -> Document -> Document
$cmin :: Document -> Document -> Document
max :: Document -> Document -> Document
$cmax :: Document -> Document -> Document
>= :: Document -> Document -> Bool
$c>= :: Document -> Document -> Bool
> :: Document -> Document -> Bool
$c> :: Document -> Document -> Bool
<= :: Document -> Document -> Bool
$c<= :: Document -> Document -> Bool
< :: Document -> Document -> Bool
$c< :: Document -> Document -> Bool
compare :: Document -> Document -> Ordering
$ccompare :: Document -> Document -> Ordering
Ord, ReadPrec [Document]
ReadPrec Document
Int -> ReadS Document
ReadS [Document]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Document]
$creadListPrec :: ReadPrec [Document]
readPrec :: ReadPrec Document
$creadPrec :: ReadPrec Document
readList :: ReadS [Document]
$creadList :: ReadS [Document]
readsPrec :: Int -> ReadS Document
$creadsPrec :: Int -> ReadS Document
Read, Int -> Document -> String -> String
[Document] -> String -> String
Document -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Document] -> String -> String
$cshowList :: [Document] -> String -> String
show :: Document -> String
$cshow :: Document -> String
showsPrec :: Int -> Document -> String -> String
$cshowsPrec :: Int -> Document -> String -> String
Show)

_Document :: Name
_Document = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Document")

data Definition = 
  DefinitionExecutable ExecutableDefinition |
  DefinitionTypeSystem TypeSystemDefinitionOrExtension
  deriving (Definition -> Definition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Definition -> Definition -> Bool
$c/= :: Definition -> Definition -> Bool
== :: Definition -> Definition -> Bool
$c== :: Definition -> Definition -> Bool
Eq, Eq Definition
Definition -> Definition -> Bool
Definition -> Definition -> Ordering
Definition -> Definition -> Definition
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
min :: Definition -> Definition -> Definition
$cmin :: Definition -> Definition -> Definition
max :: Definition -> Definition -> Definition
$cmax :: Definition -> Definition -> Definition
>= :: Definition -> Definition -> Bool
$c>= :: Definition -> Definition -> Bool
> :: Definition -> Definition -> Bool
$c> :: Definition -> Definition -> Bool
<= :: Definition -> Definition -> Bool
$c<= :: Definition -> Definition -> Bool
< :: Definition -> Definition -> Bool
$c< :: Definition -> Definition -> Bool
compare :: Definition -> Definition -> Ordering
$ccompare :: Definition -> Definition -> Ordering
Ord, ReadPrec [Definition]
ReadPrec Definition
Int -> ReadS Definition
ReadS [Definition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Definition]
$creadListPrec :: ReadPrec [Definition]
readPrec :: ReadPrec Definition
$creadPrec :: ReadPrec Definition
readList :: ReadS [Definition]
$creadList :: ReadS [Definition]
readsPrec :: Int -> ReadS Definition
$creadsPrec :: Int -> ReadS Definition
Read, Int -> Definition -> String -> String
[Definition] -> String -> String
Definition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Definition] -> String -> String
$cshowList :: [Definition] -> String -> String
show :: Definition -> String
$cshow :: Definition -> String
showsPrec :: Int -> Definition -> String -> String
$cshowsPrec :: Int -> Definition -> String -> String
Show)

_Definition :: Name
_Definition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Definition")

_Definition_executable :: FieldName
_Definition_executable = (String -> FieldName
Core.FieldName String
"executable")

_Definition_typeSystem :: FieldName
_Definition_typeSystem = (String -> FieldName
Core.FieldName String
"typeSystem")

newtype ExecutableDocument = 
  ExecutableDocument {
    ExecutableDocument -> [ExecutableDefinition]
unExecutableDocument :: [ExecutableDefinition]}
  deriving (ExecutableDocument -> ExecutableDocument -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExecutableDocument -> ExecutableDocument -> Bool
$c/= :: ExecutableDocument -> ExecutableDocument -> Bool
== :: ExecutableDocument -> ExecutableDocument -> Bool
$c== :: ExecutableDocument -> ExecutableDocument -> Bool
Eq, Eq ExecutableDocument
ExecutableDocument -> ExecutableDocument -> Bool
ExecutableDocument -> ExecutableDocument -> Ordering
ExecutableDocument -> ExecutableDocument -> ExecutableDocument
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
min :: ExecutableDocument -> ExecutableDocument -> ExecutableDocument
$cmin :: ExecutableDocument -> ExecutableDocument -> ExecutableDocument
max :: ExecutableDocument -> ExecutableDocument -> ExecutableDocument
$cmax :: ExecutableDocument -> ExecutableDocument -> ExecutableDocument
>= :: ExecutableDocument -> ExecutableDocument -> Bool
$c>= :: ExecutableDocument -> ExecutableDocument -> Bool
> :: ExecutableDocument -> ExecutableDocument -> Bool
$c> :: ExecutableDocument -> ExecutableDocument -> Bool
<= :: ExecutableDocument -> ExecutableDocument -> Bool
$c<= :: ExecutableDocument -> ExecutableDocument -> Bool
< :: ExecutableDocument -> ExecutableDocument -> Bool
$c< :: ExecutableDocument -> ExecutableDocument -> Bool
compare :: ExecutableDocument -> ExecutableDocument -> Ordering
$ccompare :: ExecutableDocument -> ExecutableDocument -> Ordering
Ord, ReadPrec [ExecutableDocument]
ReadPrec ExecutableDocument
Int -> ReadS ExecutableDocument
ReadS [ExecutableDocument]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExecutableDocument]
$creadListPrec :: ReadPrec [ExecutableDocument]
readPrec :: ReadPrec ExecutableDocument
$creadPrec :: ReadPrec ExecutableDocument
readList :: ReadS [ExecutableDocument]
$creadList :: ReadS [ExecutableDocument]
readsPrec :: Int -> ReadS ExecutableDocument
$creadsPrec :: Int -> ReadS ExecutableDocument
Read, Int -> ExecutableDocument -> String -> String
[ExecutableDocument] -> String -> String
ExecutableDocument -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ExecutableDocument] -> String -> String
$cshowList :: [ExecutableDocument] -> String -> String
show :: ExecutableDocument -> String
$cshow :: ExecutableDocument -> String
showsPrec :: Int -> ExecutableDocument -> String -> String
$cshowsPrec :: Int -> ExecutableDocument -> String -> String
Show)

_ExecutableDocument :: Name
_ExecutableDocument = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ExecutableDocument")

data ExecutableDefinition = 
  ExecutableDefinitionOperation OperationDefinition |
  ExecutableDefinitionFragment FragmentDefinition
  deriving (ExecutableDefinition -> ExecutableDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ExecutableDefinition -> ExecutableDefinition -> Bool
$c/= :: ExecutableDefinition -> ExecutableDefinition -> Bool
== :: ExecutableDefinition -> ExecutableDefinition -> Bool
$c== :: ExecutableDefinition -> ExecutableDefinition -> Bool
Eq, Eq ExecutableDefinition
ExecutableDefinition -> ExecutableDefinition -> Bool
ExecutableDefinition -> ExecutableDefinition -> Ordering
ExecutableDefinition
-> ExecutableDefinition -> ExecutableDefinition
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
min :: ExecutableDefinition
-> ExecutableDefinition -> ExecutableDefinition
$cmin :: ExecutableDefinition
-> ExecutableDefinition -> ExecutableDefinition
max :: ExecutableDefinition
-> ExecutableDefinition -> ExecutableDefinition
$cmax :: ExecutableDefinition
-> ExecutableDefinition -> ExecutableDefinition
>= :: ExecutableDefinition -> ExecutableDefinition -> Bool
$c>= :: ExecutableDefinition -> ExecutableDefinition -> Bool
> :: ExecutableDefinition -> ExecutableDefinition -> Bool
$c> :: ExecutableDefinition -> ExecutableDefinition -> Bool
<= :: ExecutableDefinition -> ExecutableDefinition -> Bool
$c<= :: ExecutableDefinition -> ExecutableDefinition -> Bool
< :: ExecutableDefinition -> ExecutableDefinition -> Bool
$c< :: ExecutableDefinition -> ExecutableDefinition -> Bool
compare :: ExecutableDefinition -> ExecutableDefinition -> Ordering
$ccompare :: ExecutableDefinition -> ExecutableDefinition -> Ordering
Ord, ReadPrec [ExecutableDefinition]
ReadPrec ExecutableDefinition
Int -> ReadS ExecutableDefinition
ReadS [ExecutableDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExecutableDefinition]
$creadListPrec :: ReadPrec [ExecutableDefinition]
readPrec :: ReadPrec ExecutableDefinition
$creadPrec :: ReadPrec ExecutableDefinition
readList :: ReadS [ExecutableDefinition]
$creadList :: ReadS [ExecutableDefinition]
readsPrec :: Int -> ReadS ExecutableDefinition
$creadsPrec :: Int -> ReadS ExecutableDefinition
Read, Int -> ExecutableDefinition -> String -> String
[ExecutableDefinition] -> String -> String
ExecutableDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ExecutableDefinition] -> String -> String
$cshowList :: [ExecutableDefinition] -> String -> String
show :: ExecutableDefinition -> String
$cshow :: ExecutableDefinition -> String
showsPrec :: Int -> ExecutableDefinition -> String -> String
$cshowsPrec :: Int -> ExecutableDefinition -> String -> String
Show)

_ExecutableDefinition :: Name
_ExecutableDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ExecutableDefinition")

_ExecutableDefinition_operation :: FieldName
_ExecutableDefinition_operation = (String -> FieldName
Core.FieldName String
"operation")

_ExecutableDefinition_fragment :: FieldName
_ExecutableDefinition_fragment = (String -> FieldName
Core.FieldName String
"fragment")

data OperationDefinition = 
  OperationDefinitionSequence OperationDefinition_Sequence |
  OperationDefinitionSelectionSet SelectionSet
  deriving (OperationDefinition -> OperationDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OperationDefinition -> OperationDefinition -> Bool
$c/= :: OperationDefinition -> OperationDefinition -> Bool
== :: OperationDefinition -> OperationDefinition -> Bool
$c== :: OperationDefinition -> OperationDefinition -> Bool
Eq, Eq OperationDefinition
OperationDefinition -> OperationDefinition -> Bool
OperationDefinition -> OperationDefinition -> Ordering
OperationDefinition -> OperationDefinition -> OperationDefinition
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
min :: OperationDefinition -> OperationDefinition -> OperationDefinition
$cmin :: OperationDefinition -> OperationDefinition -> OperationDefinition
max :: OperationDefinition -> OperationDefinition -> OperationDefinition
$cmax :: OperationDefinition -> OperationDefinition -> OperationDefinition
>= :: OperationDefinition -> OperationDefinition -> Bool
$c>= :: OperationDefinition -> OperationDefinition -> Bool
> :: OperationDefinition -> OperationDefinition -> Bool
$c> :: OperationDefinition -> OperationDefinition -> Bool
<= :: OperationDefinition -> OperationDefinition -> Bool
$c<= :: OperationDefinition -> OperationDefinition -> Bool
< :: OperationDefinition -> OperationDefinition -> Bool
$c< :: OperationDefinition -> OperationDefinition -> Bool
compare :: OperationDefinition -> OperationDefinition -> Ordering
$ccompare :: OperationDefinition -> OperationDefinition -> Ordering
Ord, ReadPrec [OperationDefinition]
ReadPrec OperationDefinition
Int -> ReadS OperationDefinition
ReadS [OperationDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OperationDefinition]
$creadListPrec :: ReadPrec [OperationDefinition]
readPrec :: ReadPrec OperationDefinition
$creadPrec :: ReadPrec OperationDefinition
readList :: ReadS [OperationDefinition]
$creadList :: ReadS [OperationDefinition]
readsPrec :: Int -> ReadS OperationDefinition
$creadsPrec :: Int -> ReadS OperationDefinition
Read, Int -> OperationDefinition -> String -> String
[OperationDefinition] -> String -> String
OperationDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [OperationDefinition] -> String -> String
$cshowList :: [OperationDefinition] -> String -> String
show :: OperationDefinition -> String
$cshow :: OperationDefinition -> String
showsPrec :: Int -> OperationDefinition -> String -> String
$cshowsPrec :: Int -> OperationDefinition -> String -> String
Show)

_OperationDefinition :: Name
_OperationDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.OperationDefinition")

_OperationDefinition_sequence :: FieldName
_OperationDefinition_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_OperationDefinition_selectionSet :: FieldName
_OperationDefinition_selectionSet = (String -> FieldName
Core.FieldName String
"selectionSet")

data OperationDefinition_Sequence = 
  OperationDefinition_Sequence {
    OperationDefinition_Sequence -> OperationType
operationDefinition_SequenceOperationType :: OperationType,
    OperationDefinition_Sequence -> Maybe Name
operationDefinition_SequenceName :: (Maybe Name),
    OperationDefinition_Sequence -> Maybe VariablesDefinition
operationDefinition_SequenceVariablesDefinition :: (Maybe VariablesDefinition),
    OperationDefinition_Sequence -> Maybe Directives
operationDefinition_SequenceDirectives :: (Maybe Directives),
    OperationDefinition_Sequence -> SelectionSet
operationDefinition_SequenceSelectionSet :: SelectionSet}
  deriving (OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
$c/= :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
== :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
$c== :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
Eq, Eq OperationDefinition_Sequence
OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Ordering
OperationDefinition_Sequence
-> OperationDefinition_Sequence -> OperationDefinition_Sequence
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
min :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> OperationDefinition_Sequence
$cmin :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> OperationDefinition_Sequence
max :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> OperationDefinition_Sequence
$cmax :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> OperationDefinition_Sequence
>= :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
$c>= :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
> :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
$c> :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
<= :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
$c<= :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
< :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
$c< :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
compare :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Ordering
$ccompare :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Ordering
Ord, ReadPrec [OperationDefinition_Sequence]
ReadPrec OperationDefinition_Sequence
Int -> ReadS OperationDefinition_Sequence
ReadS [OperationDefinition_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OperationDefinition_Sequence]
$creadListPrec :: ReadPrec [OperationDefinition_Sequence]
readPrec :: ReadPrec OperationDefinition_Sequence
$creadPrec :: ReadPrec OperationDefinition_Sequence
readList :: ReadS [OperationDefinition_Sequence]
$creadList :: ReadS [OperationDefinition_Sequence]
readsPrec :: Int -> ReadS OperationDefinition_Sequence
$creadsPrec :: Int -> ReadS OperationDefinition_Sequence
Read, Int -> OperationDefinition_Sequence -> String -> String
[OperationDefinition_Sequence] -> String -> String
OperationDefinition_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [OperationDefinition_Sequence] -> String -> String
$cshowList :: [OperationDefinition_Sequence] -> String -> String
show :: OperationDefinition_Sequence -> String
$cshow :: OperationDefinition_Sequence -> String
showsPrec :: Int -> OperationDefinition_Sequence -> String -> String
$cshowsPrec :: Int -> OperationDefinition_Sequence -> String -> String
Show)

_OperationDefinition_Sequence :: Name
_OperationDefinition_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.OperationDefinition.Sequence")

_OperationDefinition_Sequence_operationType :: FieldName
_OperationDefinition_Sequence_operationType = (String -> FieldName
Core.FieldName String
"operationType")

_OperationDefinition_Sequence_name :: FieldName
_OperationDefinition_Sequence_name = (String -> FieldName
Core.FieldName String
"name")

_OperationDefinition_Sequence_variablesDefinition :: FieldName
_OperationDefinition_Sequence_variablesDefinition = (String -> FieldName
Core.FieldName String
"variablesDefinition")

_OperationDefinition_Sequence_directives :: FieldName
_OperationDefinition_Sequence_directives = (String -> FieldName
Core.FieldName String
"directives")

_OperationDefinition_Sequence_selectionSet :: FieldName
_OperationDefinition_Sequence_selectionSet = (String -> FieldName
Core.FieldName String
"selectionSet")

data OperationType = 
  OperationTypeQuery  |
  OperationTypeMutation  |
  OperationTypeSubscription 
  deriving (OperationType -> OperationType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: OperationType -> OperationType -> Bool
$c/= :: OperationType -> OperationType -> Bool
== :: OperationType -> OperationType -> Bool
$c== :: OperationType -> OperationType -> Bool
Eq, Eq OperationType
OperationType -> OperationType -> Bool
OperationType -> OperationType -> Ordering
OperationType -> OperationType -> OperationType
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
min :: OperationType -> OperationType -> OperationType
$cmin :: OperationType -> OperationType -> OperationType
max :: OperationType -> OperationType -> OperationType
$cmax :: OperationType -> OperationType -> OperationType
>= :: OperationType -> OperationType -> Bool
$c>= :: OperationType -> OperationType -> Bool
> :: OperationType -> OperationType -> Bool
$c> :: OperationType -> OperationType -> Bool
<= :: OperationType -> OperationType -> Bool
$c<= :: OperationType -> OperationType -> Bool
< :: OperationType -> OperationType -> Bool
$c< :: OperationType -> OperationType -> Bool
compare :: OperationType -> OperationType -> Ordering
$ccompare :: OperationType -> OperationType -> Ordering
Ord, ReadPrec [OperationType]
ReadPrec OperationType
Int -> ReadS OperationType
ReadS [OperationType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [OperationType]
$creadListPrec :: ReadPrec [OperationType]
readPrec :: ReadPrec OperationType
$creadPrec :: ReadPrec OperationType
readList :: ReadS [OperationType]
$creadList :: ReadS [OperationType]
readsPrec :: Int -> ReadS OperationType
$creadsPrec :: Int -> ReadS OperationType
Read, Int -> OperationType -> String -> String
[OperationType] -> String -> String
OperationType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [OperationType] -> String -> String
$cshowList :: [OperationType] -> String -> String
show :: OperationType -> String
$cshow :: OperationType -> String
showsPrec :: Int -> OperationType -> String -> String
$cshowsPrec :: Int -> OperationType -> String -> String
Show)

_OperationType :: Name
_OperationType = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.OperationType")

_OperationType_query :: FieldName
_OperationType_query = (String -> FieldName
Core.FieldName String
"query")

_OperationType_mutation :: FieldName
_OperationType_mutation = (String -> FieldName
Core.FieldName String
"mutation")

_OperationType_subscription :: FieldName
_OperationType_subscription = (String -> FieldName
Core.FieldName String
"subscription")

data SelectionSet = 
  SelectionSet {
    SelectionSet -> [Selection]
selectionSetListOfSelection :: [Selection]}
  deriving (SelectionSet -> SelectionSet -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SelectionSet -> SelectionSet -> Bool
$c/= :: SelectionSet -> SelectionSet -> Bool
== :: SelectionSet -> SelectionSet -> Bool
$c== :: SelectionSet -> SelectionSet -> Bool
Eq, Eq SelectionSet
SelectionSet -> SelectionSet -> Bool
SelectionSet -> SelectionSet -> Ordering
SelectionSet -> SelectionSet -> SelectionSet
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
min :: SelectionSet -> SelectionSet -> SelectionSet
$cmin :: SelectionSet -> SelectionSet -> SelectionSet
max :: SelectionSet -> SelectionSet -> SelectionSet
$cmax :: SelectionSet -> SelectionSet -> SelectionSet
>= :: SelectionSet -> SelectionSet -> Bool
$c>= :: SelectionSet -> SelectionSet -> Bool
> :: SelectionSet -> SelectionSet -> Bool
$c> :: SelectionSet -> SelectionSet -> Bool
<= :: SelectionSet -> SelectionSet -> Bool
$c<= :: SelectionSet -> SelectionSet -> Bool
< :: SelectionSet -> SelectionSet -> Bool
$c< :: SelectionSet -> SelectionSet -> Bool
compare :: SelectionSet -> SelectionSet -> Ordering
$ccompare :: SelectionSet -> SelectionSet -> Ordering
Ord, ReadPrec [SelectionSet]
ReadPrec SelectionSet
Int -> ReadS SelectionSet
ReadS [SelectionSet]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SelectionSet]
$creadListPrec :: ReadPrec [SelectionSet]
readPrec :: ReadPrec SelectionSet
$creadPrec :: ReadPrec SelectionSet
readList :: ReadS [SelectionSet]
$creadList :: ReadS [SelectionSet]
readsPrec :: Int -> ReadS SelectionSet
$creadsPrec :: Int -> ReadS SelectionSet
Read, Int -> SelectionSet -> String -> String
[SelectionSet] -> String -> String
SelectionSet -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SelectionSet] -> String -> String
$cshowList :: [SelectionSet] -> String -> String
show :: SelectionSet -> String
$cshow :: SelectionSet -> String
showsPrec :: Int -> SelectionSet -> String -> String
$cshowsPrec :: Int -> SelectionSet -> String -> String
Show)

_SelectionSet :: Name
_SelectionSet = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.SelectionSet")

_SelectionSet_listOfSelection :: FieldName
_SelectionSet_listOfSelection = (String -> FieldName
Core.FieldName String
"listOfSelection")

data Selection = 
  SelectionField Field |
  SelectionFragmentSpread FragmentSpread |
  SelectionInlineFragment InlineFragment
  deriving (Selection -> Selection -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Selection -> Selection -> Bool
$c/= :: Selection -> Selection -> Bool
== :: Selection -> Selection -> Bool
$c== :: Selection -> Selection -> Bool
Eq, Eq Selection
Selection -> Selection -> Bool
Selection -> Selection -> Ordering
Selection -> Selection -> Selection
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
min :: Selection -> Selection -> Selection
$cmin :: Selection -> Selection -> Selection
max :: Selection -> Selection -> Selection
$cmax :: Selection -> Selection -> Selection
>= :: Selection -> Selection -> Bool
$c>= :: Selection -> Selection -> Bool
> :: Selection -> Selection -> Bool
$c> :: Selection -> Selection -> Bool
<= :: Selection -> Selection -> Bool
$c<= :: Selection -> Selection -> Bool
< :: Selection -> Selection -> Bool
$c< :: Selection -> Selection -> Bool
compare :: Selection -> Selection -> Ordering
$ccompare :: Selection -> Selection -> Ordering
Ord, ReadPrec [Selection]
ReadPrec Selection
Int -> ReadS Selection
ReadS [Selection]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Selection]
$creadListPrec :: ReadPrec [Selection]
readPrec :: ReadPrec Selection
$creadPrec :: ReadPrec Selection
readList :: ReadS [Selection]
$creadList :: ReadS [Selection]
readsPrec :: Int -> ReadS Selection
$creadsPrec :: Int -> ReadS Selection
Read, Int -> Selection -> String -> String
[Selection] -> String -> String
Selection -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Selection] -> String -> String
$cshowList :: [Selection] -> String -> String
show :: Selection -> String
$cshow :: Selection -> String
showsPrec :: Int -> Selection -> String -> String
$cshowsPrec :: Int -> Selection -> String -> String
Show)

_Selection :: Name
_Selection = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Selection")

_Selection_field :: FieldName
_Selection_field = (String -> FieldName
Core.FieldName String
"field")

_Selection_fragmentSpread :: FieldName
_Selection_fragmentSpread = (String -> FieldName
Core.FieldName String
"fragmentSpread")

_Selection_inlineFragment :: FieldName
_Selection_inlineFragment = (String -> FieldName
Core.FieldName String
"inlineFragment")

data Field = 
  Field {
    Field -> Maybe Alias
fieldAlias :: (Maybe Alias),
    Field -> Name
fieldName :: Name,
    Field -> Maybe Arguments
fieldArguments :: (Maybe Arguments),
    Field -> Maybe Directives
fieldDirectives :: (Maybe Directives),
    Field -> Maybe SelectionSet
fieldSelectionSet :: (Maybe SelectionSet)}
  deriving (Field -> Field -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Field -> Field -> Bool
$c/= :: Field -> Field -> Bool
== :: Field -> Field -> Bool
$c== :: Field -> Field -> Bool
Eq, Eq Field
Field -> Field -> Bool
Field -> Field -> Ordering
Field -> Field -> Field
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
min :: Field -> Field -> Field
$cmin :: Field -> Field -> Field
max :: Field -> Field -> Field
$cmax :: Field -> Field -> Field
>= :: Field -> Field -> Bool
$c>= :: Field -> Field -> Bool
> :: Field -> Field -> Bool
$c> :: Field -> Field -> Bool
<= :: Field -> Field -> Bool
$c<= :: Field -> Field -> Bool
< :: Field -> Field -> Bool
$c< :: Field -> Field -> Bool
compare :: Field -> Field -> Ordering
$ccompare :: Field -> Field -> Ordering
Ord, ReadPrec [Field]
ReadPrec Field
Int -> ReadS Field
ReadS [Field]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Field]
$creadListPrec :: ReadPrec [Field]
readPrec :: ReadPrec Field
$creadPrec :: ReadPrec Field
readList :: ReadS [Field]
$creadList :: ReadS [Field]
readsPrec :: Int -> ReadS Field
$creadsPrec :: Int -> ReadS Field
Read, Int -> Field -> String -> String
[Field] -> String -> String
Field -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Field] -> String -> String
$cshowList :: [Field] -> String -> String
show :: Field -> String
$cshow :: Field -> String
showsPrec :: Int -> Field -> String -> String
$cshowsPrec :: Int -> Field -> String -> String
Show)

_Field :: Name
_Field = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Field")

_Field_alias :: FieldName
_Field_alias = (String -> FieldName
Core.FieldName String
"alias")

_Field_name :: FieldName
_Field_name = (String -> FieldName
Core.FieldName String
"name")

_Field_arguments :: FieldName
_Field_arguments = (String -> FieldName
Core.FieldName String
"arguments")

_Field_directives :: FieldName
_Field_directives = (String -> FieldName
Core.FieldName String
"directives")

_Field_selectionSet :: FieldName
_Field_selectionSet = (String -> FieldName
Core.FieldName String
"selectionSet")

data Alias = 
  AliasName Name |
  AliasColon 
  deriving (Alias -> Alias -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Alias -> Alias -> Bool
$c/= :: Alias -> Alias -> Bool
== :: Alias -> Alias -> Bool
$c== :: Alias -> Alias -> Bool
Eq, Eq Alias
Alias -> Alias -> Bool
Alias -> Alias -> Ordering
Alias -> Alias -> Alias
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
min :: Alias -> Alias -> Alias
$cmin :: Alias -> Alias -> Alias
max :: Alias -> Alias -> Alias
$cmax :: Alias -> Alias -> Alias
>= :: Alias -> Alias -> Bool
$c>= :: Alias -> Alias -> Bool
> :: Alias -> Alias -> Bool
$c> :: Alias -> Alias -> Bool
<= :: Alias -> Alias -> Bool
$c<= :: Alias -> Alias -> Bool
< :: Alias -> Alias -> Bool
$c< :: Alias -> Alias -> Bool
compare :: Alias -> Alias -> Ordering
$ccompare :: Alias -> Alias -> Ordering
Ord, ReadPrec [Alias]
ReadPrec Alias
Int -> ReadS Alias
ReadS [Alias]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Alias]
$creadListPrec :: ReadPrec [Alias]
readPrec :: ReadPrec Alias
$creadPrec :: ReadPrec Alias
readList :: ReadS [Alias]
$creadList :: ReadS [Alias]
readsPrec :: Int -> ReadS Alias
$creadsPrec :: Int -> ReadS Alias
Read, Int -> Alias -> String -> String
[Alias] -> String -> String
Alias -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Alias] -> String -> String
$cshowList :: [Alias] -> String -> String
show :: Alias -> String
$cshow :: Alias -> String
showsPrec :: Int -> Alias -> String -> String
$cshowsPrec :: Int -> Alias -> String -> String
Show)

_Alias :: Name
_Alias = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Alias")

_Alias_name :: FieldName
_Alias_name = (String -> FieldName
Core.FieldName String
"name")

_Alias_colon :: FieldName
_Alias_colon = (String -> FieldName
Core.FieldName String
"colon")

data Arguments = 
  Arguments {
    Arguments -> [Argument]
argumentsListOfArgument :: [Argument]}
  deriving (Arguments -> Arguments -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Arguments -> Arguments -> Bool
$c/= :: Arguments -> Arguments -> Bool
== :: Arguments -> Arguments -> Bool
$c== :: Arguments -> Arguments -> Bool
Eq, Eq Arguments
Arguments -> Arguments -> Bool
Arguments -> Arguments -> Ordering
Arguments -> Arguments -> Arguments
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
min :: Arguments -> Arguments -> Arguments
$cmin :: Arguments -> Arguments -> Arguments
max :: Arguments -> Arguments -> Arguments
$cmax :: Arguments -> Arguments -> Arguments
>= :: Arguments -> Arguments -> Bool
$c>= :: Arguments -> Arguments -> Bool
> :: Arguments -> Arguments -> Bool
$c> :: Arguments -> Arguments -> Bool
<= :: Arguments -> Arguments -> Bool
$c<= :: Arguments -> Arguments -> Bool
< :: Arguments -> Arguments -> Bool
$c< :: Arguments -> Arguments -> Bool
compare :: Arguments -> Arguments -> Ordering
$ccompare :: Arguments -> Arguments -> Ordering
Ord, ReadPrec [Arguments]
ReadPrec Arguments
Int -> ReadS Arguments
ReadS [Arguments]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Arguments]
$creadListPrec :: ReadPrec [Arguments]
readPrec :: ReadPrec Arguments
$creadPrec :: ReadPrec Arguments
readList :: ReadS [Arguments]
$creadList :: ReadS [Arguments]
readsPrec :: Int -> ReadS Arguments
$creadsPrec :: Int -> ReadS Arguments
Read, Int -> Arguments -> String -> String
[Arguments] -> String -> String
Arguments -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Arguments] -> String -> String
$cshowList :: [Arguments] -> String -> String
show :: Arguments -> String
$cshow :: Arguments -> String
showsPrec :: Int -> Arguments -> String -> String
$cshowsPrec :: Int -> Arguments -> String -> String
Show)

_Arguments :: Name
_Arguments = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Arguments")

_Arguments_listOfArgument :: FieldName
_Arguments_listOfArgument = (String -> FieldName
Core.FieldName String
"listOfArgument")

data Argument = 
  Argument {
    Argument -> Name
argumentName :: Name,
    Argument -> Value
argumentValue :: Value}
  deriving (Argument -> Argument -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Argument -> Argument -> Bool
$c/= :: Argument -> Argument -> Bool
== :: Argument -> Argument -> Bool
$c== :: Argument -> Argument -> Bool
Eq, Eq Argument
Argument -> Argument -> Bool
Argument -> Argument -> Ordering
Argument -> Argument -> Argument
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
min :: Argument -> Argument -> Argument
$cmin :: Argument -> Argument -> Argument
max :: Argument -> Argument -> Argument
$cmax :: Argument -> Argument -> Argument
>= :: Argument -> Argument -> Bool
$c>= :: Argument -> Argument -> Bool
> :: Argument -> Argument -> Bool
$c> :: Argument -> Argument -> Bool
<= :: Argument -> Argument -> Bool
$c<= :: Argument -> Argument -> Bool
< :: Argument -> Argument -> Bool
$c< :: Argument -> Argument -> Bool
compare :: Argument -> Argument -> Ordering
$ccompare :: Argument -> Argument -> Ordering
Ord, ReadPrec [Argument]
ReadPrec Argument
Int -> ReadS Argument
ReadS [Argument]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Argument]
$creadListPrec :: ReadPrec [Argument]
readPrec :: ReadPrec Argument
$creadPrec :: ReadPrec Argument
readList :: ReadS [Argument]
$creadList :: ReadS [Argument]
readsPrec :: Int -> ReadS Argument
$creadsPrec :: Int -> ReadS Argument
Read, Int -> Argument -> String -> String
[Argument] -> String -> String
Argument -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Argument] -> String -> String
$cshowList :: [Argument] -> String -> String
show :: Argument -> String
$cshow :: Argument -> String
showsPrec :: Int -> Argument -> String -> String
$cshowsPrec :: Int -> Argument -> String -> String
Show)

_Argument :: Name
_Argument = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Argument")

_Argument_name :: FieldName
_Argument_name = (String -> FieldName
Core.FieldName String
"name")

_Argument_value :: FieldName
_Argument_value = (String -> FieldName
Core.FieldName String
"value")

data FragmentSpread = 
  FragmentSpread {
    FragmentSpread -> FragmentName
fragmentSpreadFragmentName :: FragmentName,
    FragmentSpread -> Maybe Directives
fragmentSpreadDirectives :: (Maybe Directives)}
  deriving (FragmentSpread -> FragmentSpread -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FragmentSpread -> FragmentSpread -> Bool
$c/= :: FragmentSpread -> FragmentSpread -> Bool
== :: FragmentSpread -> FragmentSpread -> Bool
$c== :: FragmentSpread -> FragmentSpread -> Bool
Eq, Eq FragmentSpread
FragmentSpread -> FragmentSpread -> Bool
FragmentSpread -> FragmentSpread -> Ordering
FragmentSpread -> FragmentSpread -> FragmentSpread
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
min :: FragmentSpread -> FragmentSpread -> FragmentSpread
$cmin :: FragmentSpread -> FragmentSpread -> FragmentSpread
max :: FragmentSpread -> FragmentSpread -> FragmentSpread
$cmax :: FragmentSpread -> FragmentSpread -> FragmentSpread
>= :: FragmentSpread -> FragmentSpread -> Bool
$c>= :: FragmentSpread -> FragmentSpread -> Bool
> :: FragmentSpread -> FragmentSpread -> Bool
$c> :: FragmentSpread -> FragmentSpread -> Bool
<= :: FragmentSpread -> FragmentSpread -> Bool
$c<= :: FragmentSpread -> FragmentSpread -> Bool
< :: FragmentSpread -> FragmentSpread -> Bool
$c< :: FragmentSpread -> FragmentSpread -> Bool
compare :: FragmentSpread -> FragmentSpread -> Ordering
$ccompare :: FragmentSpread -> FragmentSpread -> Ordering
Ord, ReadPrec [FragmentSpread]
ReadPrec FragmentSpread
Int -> ReadS FragmentSpread
ReadS [FragmentSpread]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FragmentSpread]
$creadListPrec :: ReadPrec [FragmentSpread]
readPrec :: ReadPrec FragmentSpread
$creadPrec :: ReadPrec FragmentSpread
readList :: ReadS [FragmentSpread]
$creadList :: ReadS [FragmentSpread]
readsPrec :: Int -> ReadS FragmentSpread
$creadsPrec :: Int -> ReadS FragmentSpread
Read, Int -> FragmentSpread -> String -> String
[FragmentSpread] -> String -> String
FragmentSpread -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FragmentSpread] -> String -> String
$cshowList :: [FragmentSpread] -> String -> String
show :: FragmentSpread -> String
$cshow :: FragmentSpread -> String
showsPrec :: Int -> FragmentSpread -> String -> String
$cshowsPrec :: Int -> FragmentSpread -> String -> String
Show)

_FragmentSpread :: Name
_FragmentSpread = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.FragmentSpread")

_FragmentSpread_fragmentName :: FieldName
_FragmentSpread_fragmentName = (String -> FieldName
Core.FieldName String
"fragmentName")

_FragmentSpread_directives :: FieldName
_FragmentSpread_directives = (String -> FieldName
Core.FieldName String
"directives")

data InlineFragment = 
  InlineFragment {
    InlineFragment -> Maybe TypeCondition
inlineFragmentTypeCondition :: (Maybe TypeCondition),
    InlineFragment -> Maybe Directives
inlineFragmentDirectives :: (Maybe Directives),
    InlineFragment -> SelectionSet
inlineFragmentSelectionSet :: SelectionSet}
  deriving (InlineFragment -> InlineFragment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InlineFragment -> InlineFragment -> Bool
$c/= :: InlineFragment -> InlineFragment -> Bool
== :: InlineFragment -> InlineFragment -> Bool
$c== :: InlineFragment -> InlineFragment -> Bool
Eq, Eq InlineFragment
InlineFragment -> InlineFragment -> Bool
InlineFragment -> InlineFragment -> Ordering
InlineFragment -> InlineFragment -> InlineFragment
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
min :: InlineFragment -> InlineFragment -> InlineFragment
$cmin :: InlineFragment -> InlineFragment -> InlineFragment
max :: InlineFragment -> InlineFragment -> InlineFragment
$cmax :: InlineFragment -> InlineFragment -> InlineFragment
>= :: InlineFragment -> InlineFragment -> Bool
$c>= :: InlineFragment -> InlineFragment -> Bool
> :: InlineFragment -> InlineFragment -> Bool
$c> :: InlineFragment -> InlineFragment -> Bool
<= :: InlineFragment -> InlineFragment -> Bool
$c<= :: InlineFragment -> InlineFragment -> Bool
< :: InlineFragment -> InlineFragment -> Bool
$c< :: InlineFragment -> InlineFragment -> Bool
compare :: InlineFragment -> InlineFragment -> Ordering
$ccompare :: InlineFragment -> InlineFragment -> Ordering
Ord, ReadPrec [InlineFragment]
ReadPrec InlineFragment
Int -> ReadS InlineFragment
ReadS [InlineFragment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InlineFragment]
$creadListPrec :: ReadPrec [InlineFragment]
readPrec :: ReadPrec InlineFragment
$creadPrec :: ReadPrec InlineFragment
readList :: ReadS [InlineFragment]
$creadList :: ReadS [InlineFragment]
readsPrec :: Int -> ReadS InlineFragment
$creadsPrec :: Int -> ReadS InlineFragment
Read, Int -> InlineFragment -> String -> String
[InlineFragment] -> String -> String
InlineFragment -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InlineFragment] -> String -> String
$cshowList :: [InlineFragment] -> String -> String
show :: InlineFragment -> String
$cshow :: InlineFragment -> String
showsPrec :: Int -> InlineFragment -> String -> String
$cshowsPrec :: Int -> InlineFragment -> String -> String
Show)

_InlineFragment :: Name
_InlineFragment = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InlineFragment")

_InlineFragment_typeCondition :: FieldName
_InlineFragment_typeCondition = (String -> FieldName
Core.FieldName String
"typeCondition")

_InlineFragment_directives :: FieldName
_InlineFragment_directives = (String -> FieldName
Core.FieldName String
"directives")

_InlineFragment_selectionSet :: FieldName
_InlineFragment_selectionSet = (String -> FieldName
Core.FieldName String
"selectionSet")

data FragmentDefinition = 
  FragmentDefinition {
    FragmentDefinition -> FragmentName
fragmentDefinitionFragmentName :: FragmentName,
    FragmentDefinition -> TypeCondition
fragmentDefinitionTypeCondition :: TypeCondition,
    FragmentDefinition -> Maybe Directives
fragmentDefinitionDirectives :: (Maybe Directives),
    FragmentDefinition -> SelectionSet
fragmentDefinitionSelectionSet :: SelectionSet}
  deriving (FragmentDefinition -> FragmentDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FragmentDefinition -> FragmentDefinition -> Bool
$c/= :: FragmentDefinition -> FragmentDefinition -> Bool
== :: FragmentDefinition -> FragmentDefinition -> Bool
$c== :: FragmentDefinition -> FragmentDefinition -> Bool
Eq, Eq FragmentDefinition
FragmentDefinition -> FragmentDefinition -> Bool
FragmentDefinition -> FragmentDefinition -> Ordering
FragmentDefinition -> FragmentDefinition -> FragmentDefinition
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
min :: FragmentDefinition -> FragmentDefinition -> FragmentDefinition
$cmin :: FragmentDefinition -> FragmentDefinition -> FragmentDefinition
max :: FragmentDefinition -> FragmentDefinition -> FragmentDefinition
$cmax :: FragmentDefinition -> FragmentDefinition -> FragmentDefinition
>= :: FragmentDefinition -> FragmentDefinition -> Bool
$c>= :: FragmentDefinition -> FragmentDefinition -> Bool
> :: FragmentDefinition -> FragmentDefinition -> Bool
$c> :: FragmentDefinition -> FragmentDefinition -> Bool
<= :: FragmentDefinition -> FragmentDefinition -> Bool
$c<= :: FragmentDefinition -> FragmentDefinition -> Bool
< :: FragmentDefinition -> FragmentDefinition -> Bool
$c< :: FragmentDefinition -> FragmentDefinition -> Bool
compare :: FragmentDefinition -> FragmentDefinition -> Ordering
$ccompare :: FragmentDefinition -> FragmentDefinition -> Ordering
Ord, ReadPrec [FragmentDefinition]
ReadPrec FragmentDefinition
Int -> ReadS FragmentDefinition
ReadS [FragmentDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FragmentDefinition]
$creadListPrec :: ReadPrec [FragmentDefinition]
readPrec :: ReadPrec FragmentDefinition
$creadPrec :: ReadPrec FragmentDefinition
readList :: ReadS [FragmentDefinition]
$creadList :: ReadS [FragmentDefinition]
readsPrec :: Int -> ReadS FragmentDefinition
$creadsPrec :: Int -> ReadS FragmentDefinition
Read, Int -> FragmentDefinition -> String -> String
[FragmentDefinition] -> String -> String
FragmentDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FragmentDefinition] -> String -> String
$cshowList :: [FragmentDefinition] -> String -> String
show :: FragmentDefinition -> String
$cshow :: FragmentDefinition -> String
showsPrec :: Int -> FragmentDefinition -> String -> String
$cshowsPrec :: Int -> FragmentDefinition -> String -> String
Show)

_FragmentDefinition :: Name
_FragmentDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.FragmentDefinition")

_FragmentDefinition_fragmentName :: FieldName
_FragmentDefinition_fragmentName = (String -> FieldName
Core.FieldName String
"fragmentName")

_FragmentDefinition_typeCondition :: FieldName
_FragmentDefinition_typeCondition = (String -> FieldName
Core.FieldName String
"typeCondition")

_FragmentDefinition_directives :: FieldName
_FragmentDefinition_directives = (String -> FieldName
Core.FieldName String
"directives")

_FragmentDefinition_selectionSet :: FieldName
_FragmentDefinition_selectionSet = (String -> FieldName
Core.FieldName String
"selectionSet")

newtype FragmentName = 
  FragmentName {
    FragmentName -> Name
unFragmentName :: Name}
  deriving (FragmentName -> FragmentName -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FragmentName -> FragmentName -> Bool
$c/= :: FragmentName -> FragmentName -> Bool
== :: FragmentName -> FragmentName -> Bool
$c== :: FragmentName -> FragmentName -> Bool
Eq, Eq FragmentName
FragmentName -> FragmentName -> Bool
FragmentName -> FragmentName -> Ordering
FragmentName -> FragmentName -> FragmentName
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
min :: FragmentName -> FragmentName -> FragmentName
$cmin :: FragmentName -> FragmentName -> FragmentName
max :: FragmentName -> FragmentName -> FragmentName
$cmax :: FragmentName -> FragmentName -> FragmentName
>= :: FragmentName -> FragmentName -> Bool
$c>= :: FragmentName -> FragmentName -> Bool
> :: FragmentName -> FragmentName -> Bool
$c> :: FragmentName -> FragmentName -> Bool
<= :: FragmentName -> FragmentName -> Bool
$c<= :: FragmentName -> FragmentName -> Bool
< :: FragmentName -> FragmentName -> Bool
$c< :: FragmentName -> FragmentName -> Bool
compare :: FragmentName -> FragmentName -> Ordering
$ccompare :: FragmentName -> FragmentName -> Ordering
Ord, ReadPrec [FragmentName]
ReadPrec FragmentName
Int -> ReadS FragmentName
ReadS [FragmentName]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FragmentName]
$creadListPrec :: ReadPrec [FragmentName]
readPrec :: ReadPrec FragmentName
$creadPrec :: ReadPrec FragmentName
readList :: ReadS [FragmentName]
$creadList :: ReadS [FragmentName]
readsPrec :: Int -> ReadS FragmentName
$creadsPrec :: Int -> ReadS FragmentName
Read, Int -> FragmentName -> String -> String
[FragmentName] -> String -> String
FragmentName -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FragmentName] -> String -> String
$cshowList :: [FragmentName] -> String -> String
show :: FragmentName -> String
$cshow :: FragmentName -> String
showsPrec :: Int -> FragmentName -> String -> String
$cshowsPrec :: Int -> FragmentName -> String -> String
Show)

_FragmentName :: Name
_FragmentName = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.FragmentName")

data TypeCondition = 
  TypeConditionOn  |
  TypeConditionNamedType NamedType
  deriving (TypeCondition -> TypeCondition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeCondition -> TypeCondition -> Bool
$c/= :: TypeCondition -> TypeCondition -> Bool
== :: TypeCondition -> TypeCondition -> Bool
$c== :: TypeCondition -> TypeCondition -> Bool
Eq, Eq TypeCondition
TypeCondition -> TypeCondition -> Bool
TypeCondition -> TypeCondition -> Ordering
TypeCondition -> TypeCondition -> TypeCondition
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
min :: TypeCondition -> TypeCondition -> TypeCondition
$cmin :: TypeCondition -> TypeCondition -> TypeCondition
max :: TypeCondition -> TypeCondition -> TypeCondition
$cmax :: TypeCondition -> TypeCondition -> TypeCondition
>= :: TypeCondition -> TypeCondition -> Bool
$c>= :: TypeCondition -> TypeCondition -> Bool
> :: TypeCondition -> TypeCondition -> Bool
$c> :: TypeCondition -> TypeCondition -> Bool
<= :: TypeCondition -> TypeCondition -> Bool
$c<= :: TypeCondition -> TypeCondition -> Bool
< :: TypeCondition -> TypeCondition -> Bool
$c< :: TypeCondition -> TypeCondition -> Bool
compare :: TypeCondition -> TypeCondition -> Ordering
$ccompare :: TypeCondition -> TypeCondition -> Ordering
Ord, ReadPrec [TypeCondition]
ReadPrec TypeCondition
Int -> ReadS TypeCondition
ReadS [TypeCondition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeCondition]
$creadListPrec :: ReadPrec [TypeCondition]
readPrec :: ReadPrec TypeCondition
$creadPrec :: ReadPrec TypeCondition
readList :: ReadS [TypeCondition]
$creadList :: ReadS [TypeCondition]
readsPrec :: Int -> ReadS TypeCondition
$creadsPrec :: Int -> ReadS TypeCondition
Read, Int -> TypeCondition -> String -> String
[TypeCondition] -> String -> String
TypeCondition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeCondition] -> String -> String
$cshowList :: [TypeCondition] -> String -> String
show :: TypeCondition -> String
$cshow :: TypeCondition -> String
showsPrec :: Int -> TypeCondition -> String -> String
$cshowsPrec :: Int -> TypeCondition -> String -> String
Show)

_TypeCondition :: Name
_TypeCondition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.TypeCondition")

_TypeCondition_on :: FieldName
_TypeCondition_on = (String -> FieldName
Core.FieldName String
"on")

_TypeCondition_namedType :: FieldName
_TypeCondition_namedType = (String -> FieldName
Core.FieldName String
"namedType")

data Value = 
  ValueVariable Variable |
  ValueInt IntValue |
  ValueFloat FloatValue |
  ValueString StringValue |
  ValueBoolean BooleanValue |
  ValueNull NullValue |
  ValueEnum EnumValue |
  ValueList ListValue |
  ValueObject ObjectValue
  deriving (Value -> Value -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Value -> Value -> Bool
$c/= :: Value -> Value -> Bool
== :: Value -> Value -> Bool
$c== :: Value -> Value -> Bool
Eq, Eq Value
Value -> Value -> Bool
Value -> Value -> Ordering
Value -> Value -> Value
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
min :: Value -> Value -> Value
$cmin :: Value -> Value -> Value
max :: Value -> Value -> Value
$cmax :: Value -> Value -> Value
>= :: Value -> Value -> Bool
$c>= :: Value -> Value -> Bool
> :: Value -> Value -> Bool
$c> :: Value -> Value -> Bool
<= :: Value -> Value -> Bool
$c<= :: Value -> Value -> Bool
< :: Value -> Value -> Bool
$c< :: Value -> Value -> Bool
compare :: Value -> Value -> Ordering
$ccompare :: Value -> Value -> Ordering
Ord, ReadPrec [Value]
ReadPrec Value
Int -> ReadS Value
ReadS [Value]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Value]
$creadListPrec :: ReadPrec [Value]
readPrec :: ReadPrec Value
$creadPrec :: ReadPrec Value
readList :: ReadS [Value]
$creadList :: ReadS [Value]
readsPrec :: Int -> ReadS Value
$creadsPrec :: Int -> ReadS Value
Read, Int -> Value -> String -> String
[Value] -> String -> String
Value -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Value] -> String -> String
$cshowList :: [Value] -> String -> String
show :: Value -> String
$cshow :: Value -> String
showsPrec :: Int -> Value -> String -> String
$cshowsPrec :: Int -> Value -> String -> String
Show)

_Value :: Name
_Value = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Value")

_Value_variable :: FieldName
_Value_variable = (String -> FieldName
Core.FieldName String
"variable")

_Value_int :: FieldName
_Value_int = (String -> FieldName
Core.FieldName String
"int")

_Value_float :: FieldName
_Value_float = (String -> FieldName
Core.FieldName String
"float")

_Value_string :: FieldName
_Value_string = (String -> FieldName
Core.FieldName String
"string")

_Value_boolean :: FieldName
_Value_boolean = (String -> FieldName
Core.FieldName String
"boolean")

_Value_null :: FieldName
_Value_null = (String -> FieldName
Core.FieldName String
"null")

_Value_enum :: FieldName
_Value_enum = (String -> FieldName
Core.FieldName String
"enum")

_Value_list :: FieldName
_Value_list = (String -> FieldName
Core.FieldName String
"list")

_Value_object :: FieldName
_Value_object = (String -> FieldName
Core.FieldName String
"object")

data BooleanValue = 
  BooleanValueTrue  |
  BooleanValueFalse 
  deriving (BooleanValue -> BooleanValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BooleanValue -> BooleanValue -> Bool
$c/= :: BooleanValue -> BooleanValue -> Bool
== :: BooleanValue -> BooleanValue -> Bool
$c== :: BooleanValue -> BooleanValue -> Bool
Eq, Eq BooleanValue
BooleanValue -> BooleanValue -> Bool
BooleanValue -> BooleanValue -> Ordering
BooleanValue -> BooleanValue -> BooleanValue
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
min :: BooleanValue -> BooleanValue -> BooleanValue
$cmin :: BooleanValue -> BooleanValue -> BooleanValue
max :: BooleanValue -> BooleanValue -> BooleanValue
$cmax :: BooleanValue -> BooleanValue -> BooleanValue
>= :: BooleanValue -> BooleanValue -> Bool
$c>= :: BooleanValue -> BooleanValue -> Bool
> :: BooleanValue -> BooleanValue -> Bool
$c> :: BooleanValue -> BooleanValue -> Bool
<= :: BooleanValue -> BooleanValue -> Bool
$c<= :: BooleanValue -> BooleanValue -> Bool
< :: BooleanValue -> BooleanValue -> Bool
$c< :: BooleanValue -> BooleanValue -> Bool
compare :: BooleanValue -> BooleanValue -> Ordering
$ccompare :: BooleanValue -> BooleanValue -> Ordering
Ord, ReadPrec [BooleanValue]
ReadPrec BooleanValue
Int -> ReadS BooleanValue
ReadS [BooleanValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [BooleanValue]
$creadListPrec :: ReadPrec [BooleanValue]
readPrec :: ReadPrec BooleanValue
$creadPrec :: ReadPrec BooleanValue
readList :: ReadS [BooleanValue]
$creadList :: ReadS [BooleanValue]
readsPrec :: Int -> ReadS BooleanValue
$creadsPrec :: Int -> ReadS BooleanValue
Read, Int -> BooleanValue -> String -> String
[BooleanValue] -> String -> String
BooleanValue -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [BooleanValue] -> String -> String
$cshowList :: [BooleanValue] -> String -> String
show :: BooleanValue -> String
$cshow :: BooleanValue -> String
showsPrec :: Int -> BooleanValue -> String -> String
$cshowsPrec :: Int -> BooleanValue -> String -> String
Show)

_BooleanValue :: Name
_BooleanValue = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.BooleanValue")

_BooleanValue_true :: FieldName
_BooleanValue_true = (String -> FieldName
Core.FieldName String
"true")

_BooleanValue_false :: FieldName
_BooleanValue_false = (String -> FieldName
Core.FieldName String
"false")

data NullValue = 
  NullValue {}
  deriving (NullValue -> NullValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NullValue -> NullValue -> Bool
$c/= :: NullValue -> NullValue -> Bool
== :: NullValue -> NullValue -> Bool
$c== :: NullValue -> NullValue -> Bool
Eq, Eq NullValue
NullValue -> NullValue -> Bool
NullValue -> NullValue -> Ordering
NullValue -> NullValue -> NullValue
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
min :: NullValue -> NullValue -> NullValue
$cmin :: NullValue -> NullValue -> NullValue
max :: NullValue -> NullValue -> NullValue
$cmax :: NullValue -> NullValue -> NullValue
>= :: NullValue -> NullValue -> Bool
$c>= :: NullValue -> NullValue -> Bool
> :: NullValue -> NullValue -> Bool
$c> :: NullValue -> NullValue -> Bool
<= :: NullValue -> NullValue -> Bool
$c<= :: NullValue -> NullValue -> Bool
< :: NullValue -> NullValue -> Bool
$c< :: NullValue -> NullValue -> Bool
compare :: NullValue -> NullValue -> Ordering
$ccompare :: NullValue -> NullValue -> Ordering
Ord, ReadPrec [NullValue]
ReadPrec NullValue
Int -> ReadS NullValue
ReadS [NullValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NullValue]
$creadListPrec :: ReadPrec [NullValue]
readPrec :: ReadPrec NullValue
$creadPrec :: ReadPrec NullValue
readList :: ReadS [NullValue]
$creadList :: ReadS [NullValue]
readsPrec :: Int -> ReadS NullValue
$creadsPrec :: Int -> ReadS NullValue
Read, Int -> NullValue -> String -> String
[NullValue] -> String -> String
NullValue -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [NullValue] -> String -> String
$cshowList :: [NullValue] -> String -> String
show :: NullValue -> String
$cshow :: NullValue -> String
showsPrec :: Int -> NullValue -> String -> String
$cshowsPrec :: Int -> NullValue -> String -> String
Show)

_NullValue :: Name
_NullValue = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.NullValue")

data EnumValue = 
  EnumValue {
    EnumValue -> Name
enumValueName :: Name}
  deriving (EnumValue -> EnumValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumValue -> EnumValue -> Bool
$c/= :: EnumValue -> EnumValue -> Bool
== :: EnumValue -> EnumValue -> Bool
$c== :: EnumValue -> EnumValue -> Bool
Eq, Eq EnumValue
EnumValue -> EnumValue -> Bool
EnumValue -> EnumValue -> Ordering
EnumValue -> EnumValue -> EnumValue
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
min :: EnumValue -> EnumValue -> EnumValue
$cmin :: EnumValue -> EnumValue -> EnumValue
max :: EnumValue -> EnumValue -> EnumValue
$cmax :: EnumValue -> EnumValue -> EnumValue
>= :: EnumValue -> EnumValue -> Bool
$c>= :: EnumValue -> EnumValue -> Bool
> :: EnumValue -> EnumValue -> Bool
$c> :: EnumValue -> EnumValue -> Bool
<= :: EnumValue -> EnumValue -> Bool
$c<= :: EnumValue -> EnumValue -> Bool
< :: EnumValue -> EnumValue -> Bool
$c< :: EnumValue -> EnumValue -> Bool
compare :: EnumValue -> EnumValue -> Ordering
$ccompare :: EnumValue -> EnumValue -> Ordering
Ord, ReadPrec [EnumValue]
ReadPrec EnumValue
Int -> ReadS EnumValue
ReadS [EnumValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumValue]
$creadListPrec :: ReadPrec [EnumValue]
readPrec :: ReadPrec EnumValue
$creadPrec :: ReadPrec EnumValue
readList :: ReadS [EnumValue]
$creadList :: ReadS [EnumValue]
readsPrec :: Int -> ReadS EnumValue
$creadsPrec :: Int -> ReadS EnumValue
Read, Int -> EnumValue -> String -> String
[EnumValue] -> String -> String
EnumValue -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumValue] -> String -> String
$cshowList :: [EnumValue] -> String -> String
show :: EnumValue -> String
$cshow :: EnumValue -> String
showsPrec :: Int -> EnumValue -> String -> String
$cshowsPrec :: Int -> EnumValue -> String -> String
Show)

_EnumValue :: Name
_EnumValue = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.EnumValue")

_EnumValue_name :: FieldName
_EnumValue_name = (String -> FieldName
Core.FieldName String
"name")

data ListValue = 
  ListValueSequence ListValue_Sequence |
  ListValueSequence2 ListValue_Sequence2
  deriving (ListValue -> ListValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListValue -> ListValue -> Bool
$c/= :: ListValue -> ListValue -> Bool
== :: ListValue -> ListValue -> Bool
$c== :: ListValue -> ListValue -> Bool
Eq, Eq ListValue
ListValue -> ListValue -> Bool
ListValue -> ListValue -> Ordering
ListValue -> ListValue -> ListValue
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
min :: ListValue -> ListValue -> ListValue
$cmin :: ListValue -> ListValue -> ListValue
max :: ListValue -> ListValue -> ListValue
$cmax :: ListValue -> ListValue -> ListValue
>= :: ListValue -> ListValue -> Bool
$c>= :: ListValue -> ListValue -> Bool
> :: ListValue -> ListValue -> Bool
$c> :: ListValue -> ListValue -> Bool
<= :: ListValue -> ListValue -> Bool
$c<= :: ListValue -> ListValue -> Bool
< :: ListValue -> ListValue -> Bool
$c< :: ListValue -> ListValue -> Bool
compare :: ListValue -> ListValue -> Ordering
$ccompare :: ListValue -> ListValue -> Ordering
Ord, ReadPrec [ListValue]
ReadPrec ListValue
Int -> ReadS ListValue
ReadS [ListValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListValue]
$creadListPrec :: ReadPrec [ListValue]
readPrec :: ReadPrec ListValue
$creadPrec :: ReadPrec ListValue
readList :: ReadS [ListValue]
$creadList :: ReadS [ListValue]
readsPrec :: Int -> ReadS ListValue
$creadsPrec :: Int -> ReadS ListValue
Read, Int -> ListValue -> String -> String
[ListValue] -> String -> String
ListValue -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ListValue] -> String -> String
$cshowList :: [ListValue] -> String -> String
show :: ListValue -> String
$cshow :: ListValue -> String
showsPrec :: Int -> ListValue -> String -> String
$cshowsPrec :: Int -> ListValue -> String -> String
Show)

_ListValue :: Name
_ListValue = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ListValue")

_ListValue_sequence :: FieldName
_ListValue_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_ListValue_sequence2 :: FieldName
_ListValue_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data ListValue_Sequence = 
  ListValue_Sequence {}
  deriving (ListValue_Sequence -> ListValue_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListValue_Sequence -> ListValue_Sequence -> Bool
$c/= :: ListValue_Sequence -> ListValue_Sequence -> Bool
== :: ListValue_Sequence -> ListValue_Sequence -> Bool
$c== :: ListValue_Sequence -> ListValue_Sequence -> Bool
Eq, Eq ListValue_Sequence
ListValue_Sequence -> ListValue_Sequence -> Bool
ListValue_Sequence -> ListValue_Sequence -> Ordering
ListValue_Sequence -> ListValue_Sequence -> ListValue_Sequence
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
min :: ListValue_Sequence -> ListValue_Sequence -> ListValue_Sequence
$cmin :: ListValue_Sequence -> ListValue_Sequence -> ListValue_Sequence
max :: ListValue_Sequence -> ListValue_Sequence -> ListValue_Sequence
$cmax :: ListValue_Sequence -> ListValue_Sequence -> ListValue_Sequence
>= :: ListValue_Sequence -> ListValue_Sequence -> Bool
$c>= :: ListValue_Sequence -> ListValue_Sequence -> Bool
> :: ListValue_Sequence -> ListValue_Sequence -> Bool
$c> :: ListValue_Sequence -> ListValue_Sequence -> Bool
<= :: ListValue_Sequence -> ListValue_Sequence -> Bool
$c<= :: ListValue_Sequence -> ListValue_Sequence -> Bool
< :: ListValue_Sequence -> ListValue_Sequence -> Bool
$c< :: ListValue_Sequence -> ListValue_Sequence -> Bool
compare :: ListValue_Sequence -> ListValue_Sequence -> Ordering
$ccompare :: ListValue_Sequence -> ListValue_Sequence -> Ordering
Ord, ReadPrec [ListValue_Sequence]
ReadPrec ListValue_Sequence
Int -> ReadS ListValue_Sequence
ReadS [ListValue_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListValue_Sequence]
$creadListPrec :: ReadPrec [ListValue_Sequence]
readPrec :: ReadPrec ListValue_Sequence
$creadPrec :: ReadPrec ListValue_Sequence
readList :: ReadS [ListValue_Sequence]
$creadList :: ReadS [ListValue_Sequence]
readsPrec :: Int -> ReadS ListValue_Sequence
$creadsPrec :: Int -> ReadS ListValue_Sequence
Read, Int -> ListValue_Sequence -> String -> String
[ListValue_Sequence] -> String -> String
ListValue_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ListValue_Sequence] -> String -> String
$cshowList :: [ListValue_Sequence] -> String -> String
show :: ListValue_Sequence -> String
$cshow :: ListValue_Sequence -> String
showsPrec :: Int -> ListValue_Sequence -> String -> String
$cshowsPrec :: Int -> ListValue_Sequence -> String -> String
Show)

_ListValue_Sequence :: Name
_ListValue_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ListValue.Sequence")

data ListValue_Sequence2 = 
  ListValue_Sequence2 {
    ListValue_Sequence2 -> [Value]
listValue_Sequence2ListOfValue :: [Value]}
  deriving (ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
$c/= :: ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
== :: ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
$c== :: ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
Eq, Eq ListValue_Sequence2
ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
ListValue_Sequence2 -> ListValue_Sequence2 -> Ordering
ListValue_Sequence2 -> ListValue_Sequence2 -> ListValue_Sequence2
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
min :: ListValue_Sequence2 -> ListValue_Sequence2 -> ListValue_Sequence2
$cmin :: ListValue_Sequence2 -> ListValue_Sequence2 -> ListValue_Sequence2
max :: ListValue_Sequence2 -> ListValue_Sequence2 -> ListValue_Sequence2
$cmax :: ListValue_Sequence2 -> ListValue_Sequence2 -> ListValue_Sequence2
>= :: ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
$c>= :: ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
> :: ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
$c> :: ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
<= :: ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
$c<= :: ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
< :: ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
$c< :: ListValue_Sequence2 -> ListValue_Sequence2 -> Bool
compare :: ListValue_Sequence2 -> ListValue_Sequence2 -> Ordering
$ccompare :: ListValue_Sequence2 -> ListValue_Sequence2 -> Ordering
Ord, ReadPrec [ListValue_Sequence2]
ReadPrec ListValue_Sequence2
Int -> ReadS ListValue_Sequence2
ReadS [ListValue_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListValue_Sequence2]
$creadListPrec :: ReadPrec [ListValue_Sequence2]
readPrec :: ReadPrec ListValue_Sequence2
$creadPrec :: ReadPrec ListValue_Sequence2
readList :: ReadS [ListValue_Sequence2]
$creadList :: ReadS [ListValue_Sequence2]
readsPrec :: Int -> ReadS ListValue_Sequence2
$creadsPrec :: Int -> ReadS ListValue_Sequence2
Read, Int -> ListValue_Sequence2 -> String -> String
[ListValue_Sequence2] -> String -> String
ListValue_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ListValue_Sequence2] -> String -> String
$cshowList :: [ListValue_Sequence2] -> String -> String
show :: ListValue_Sequence2 -> String
$cshow :: ListValue_Sequence2 -> String
showsPrec :: Int -> ListValue_Sequence2 -> String -> String
$cshowsPrec :: Int -> ListValue_Sequence2 -> String -> String
Show)

_ListValue_Sequence2 :: Name
_ListValue_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ListValue.Sequence2")

_ListValue_Sequence2_listOfValue :: FieldName
_ListValue_Sequence2_listOfValue = (String -> FieldName
Core.FieldName String
"listOfValue")

data ObjectValue = 
  ObjectValueSequence ObjectValue_Sequence |
  ObjectValueSequence2 ObjectValue_Sequence2
  deriving (ObjectValue -> ObjectValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectValue -> ObjectValue -> Bool
$c/= :: ObjectValue -> ObjectValue -> Bool
== :: ObjectValue -> ObjectValue -> Bool
$c== :: ObjectValue -> ObjectValue -> Bool
Eq, Eq ObjectValue
ObjectValue -> ObjectValue -> Bool
ObjectValue -> ObjectValue -> Ordering
ObjectValue -> ObjectValue -> ObjectValue
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
min :: ObjectValue -> ObjectValue -> ObjectValue
$cmin :: ObjectValue -> ObjectValue -> ObjectValue
max :: ObjectValue -> ObjectValue -> ObjectValue
$cmax :: ObjectValue -> ObjectValue -> ObjectValue
>= :: ObjectValue -> ObjectValue -> Bool
$c>= :: ObjectValue -> ObjectValue -> Bool
> :: ObjectValue -> ObjectValue -> Bool
$c> :: ObjectValue -> ObjectValue -> Bool
<= :: ObjectValue -> ObjectValue -> Bool
$c<= :: ObjectValue -> ObjectValue -> Bool
< :: ObjectValue -> ObjectValue -> Bool
$c< :: ObjectValue -> ObjectValue -> Bool
compare :: ObjectValue -> ObjectValue -> Ordering
$ccompare :: ObjectValue -> ObjectValue -> Ordering
Ord, ReadPrec [ObjectValue]
ReadPrec ObjectValue
Int -> ReadS ObjectValue
ReadS [ObjectValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjectValue]
$creadListPrec :: ReadPrec [ObjectValue]
readPrec :: ReadPrec ObjectValue
$creadPrec :: ReadPrec ObjectValue
readList :: ReadS [ObjectValue]
$creadList :: ReadS [ObjectValue]
readsPrec :: Int -> ReadS ObjectValue
$creadsPrec :: Int -> ReadS ObjectValue
Read, Int -> ObjectValue -> String -> String
[ObjectValue] -> String -> String
ObjectValue -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ObjectValue] -> String -> String
$cshowList :: [ObjectValue] -> String -> String
show :: ObjectValue -> String
$cshow :: ObjectValue -> String
showsPrec :: Int -> ObjectValue -> String -> String
$cshowsPrec :: Int -> ObjectValue -> String -> String
Show)

_ObjectValue :: Name
_ObjectValue = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ObjectValue")

_ObjectValue_sequence :: FieldName
_ObjectValue_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_ObjectValue_sequence2 :: FieldName
_ObjectValue_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data ObjectValue_Sequence = 
  ObjectValue_Sequence {}
  deriving (ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
$c/= :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
== :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
$c== :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
Eq, Eq ObjectValue_Sequence
ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
ObjectValue_Sequence -> ObjectValue_Sequence -> Ordering
ObjectValue_Sequence
-> ObjectValue_Sequence -> ObjectValue_Sequence
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
min :: ObjectValue_Sequence
-> ObjectValue_Sequence -> ObjectValue_Sequence
$cmin :: ObjectValue_Sequence
-> ObjectValue_Sequence -> ObjectValue_Sequence
max :: ObjectValue_Sequence
-> ObjectValue_Sequence -> ObjectValue_Sequence
$cmax :: ObjectValue_Sequence
-> ObjectValue_Sequence -> ObjectValue_Sequence
>= :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
$c>= :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
> :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
$c> :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
<= :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
$c<= :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
< :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
$c< :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
compare :: ObjectValue_Sequence -> ObjectValue_Sequence -> Ordering
$ccompare :: ObjectValue_Sequence -> ObjectValue_Sequence -> Ordering
Ord, ReadPrec [ObjectValue_Sequence]
ReadPrec ObjectValue_Sequence
Int -> ReadS ObjectValue_Sequence
ReadS [ObjectValue_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjectValue_Sequence]
$creadListPrec :: ReadPrec [ObjectValue_Sequence]
readPrec :: ReadPrec ObjectValue_Sequence
$creadPrec :: ReadPrec ObjectValue_Sequence
readList :: ReadS [ObjectValue_Sequence]
$creadList :: ReadS [ObjectValue_Sequence]
readsPrec :: Int -> ReadS ObjectValue_Sequence
$creadsPrec :: Int -> ReadS ObjectValue_Sequence
Read, Int -> ObjectValue_Sequence -> String -> String
[ObjectValue_Sequence] -> String -> String
ObjectValue_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ObjectValue_Sequence] -> String -> String
$cshowList :: [ObjectValue_Sequence] -> String -> String
show :: ObjectValue_Sequence -> String
$cshow :: ObjectValue_Sequence -> String
showsPrec :: Int -> ObjectValue_Sequence -> String -> String
$cshowsPrec :: Int -> ObjectValue_Sequence -> String -> String
Show)

_ObjectValue_Sequence :: Name
_ObjectValue_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ObjectValue.Sequence")

data ObjectValue_Sequence2 = 
  ObjectValue_Sequence2 {
    ObjectValue_Sequence2 -> [ObjectField]
objectValue_Sequence2ListOfObjectField :: [ObjectField]}
  deriving (ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
$c/= :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
== :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
$c== :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
Eq, Eq ObjectValue_Sequence2
ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Ordering
ObjectValue_Sequence2
-> ObjectValue_Sequence2 -> ObjectValue_Sequence2
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
min :: ObjectValue_Sequence2
-> ObjectValue_Sequence2 -> ObjectValue_Sequence2
$cmin :: ObjectValue_Sequence2
-> ObjectValue_Sequence2 -> ObjectValue_Sequence2
max :: ObjectValue_Sequence2
-> ObjectValue_Sequence2 -> ObjectValue_Sequence2
$cmax :: ObjectValue_Sequence2
-> ObjectValue_Sequence2 -> ObjectValue_Sequence2
>= :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
$c>= :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
> :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
$c> :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
<= :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
$c<= :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
< :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
$c< :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Bool
compare :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Ordering
$ccompare :: ObjectValue_Sequence2 -> ObjectValue_Sequence2 -> Ordering
Ord, ReadPrec [ObjectValue_Sequence2]
ReadPrec ObjectValue_Sequence2
Int -> ReadS ObjectValue_Sequence2
ReadS [ObjectValue_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjectValue_Sequence2]
$creadListPrec :: ReadPrec [ObjectValue_Sequence2]
readPrec :: ReadPrec ObjectValue_Sequence2
$creadPrec :: ReadPrec ObjectValue_Sequence2
readList :: ReadS [ObjectValue_Sequence2]
$creadList :: ReadS [ObjectValue_Sequence2]
readsPrec :: Int -> ReadS ObjectValue_Sequence2
$creadsPrec :: Int -> ReadS ObjectValue_Sequence2
Read, Int -> ObjectValue_Sequence2 -> String -> String
[ObjectValue_Sequence2] -> String -> String
ObjectValue_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ObjectValue_Sequence2] -> String -> String
$cshowList :: [ObjectValue_Sequence2] -> String -> String
show :: ObjectValue_Sequence2 -> String
$cshow :: ObjectValue_Sequence2 -> String
showsPrec :: Int -> ObjectValue_Sequence2 -> String -> String
$cshowsPrec :: Int -> ObjectValue_Sequence2 -> String -> String
Show)

_ObjectValue_Sequence2 :: Name
_ObjectValue_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ObjectValue.Sequence2")

_ObjectValue_Sequence2_listOfObjectField :: FieldName
_ObjectValue_Sequence2_listOfObjectField = (String -> FieldName
Core.FieldName String
"listOfObjectField")

data ObjectField = 
  ObjectField {
    ObjectField -> Name
objectFieldName :: Name,
    ObjectField -> Value
objectFieldValue :: Value}
  deriving (ObjectField -> ObjectField -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectField -> ObjectField -> Bool
$c/= :: ObjectField -> ObjectField -> Bool
== :: ObjectField -> ObjectField -> Bool
$c== :: ObjectField -> ObjectField -> Bool
Eq, Eq ObjectField
ObjectField -> ObjectField -> Bool
ObjectField -> ObjectField -> Ordering
ObjectField -> ObjectField -> ObjectField
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
min :: ObjectField -> ObjectField -> ObjectField
$cmin :: ObjectField -> ObjectField -> ObjectField
max :: ObjectField -> ObjectField -> ObjectField
$cmax :: ObjectField -> ObjectField -> ObjectField
>= :: ObjectField -> ObjectField -> Bool
$c>= :: ObjectField -> ObjectField -> Bool
> :: ObjectField -> ObjectField -> Bool
$c> :: ObjectField -> ObjectField -> Bool
<= :: ObjectField -> ObjectField -> Bool
$c<= :: ObjectField -> ObjectField -> Bool
< :: ObjectField -> ObjectField -> Bool
$c< :: ObjectField -> ObjectField -> Bool
compare :: ObjectField -> ObjectField -> Ordering
$ccompare :: ObjectField -> ObjectField -> Ordering
Ord, ReadPrec [ObjectField]
ReadPrec ObjectField
Int -> ReadS ObjectField
ReadS [ObjectField]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjectField]
$creadListPrec :: ReadPrec [ObjectField]
readPrec :: ReadPrec ObjectField
$creadPrec :: ReadPrec ObjectField
readList :: ReadS [ObjectField]
$creadList :: ReadS [ObjectField]
readsPrec :: Int -> ReadS ObjectField
$creadsPrec :: Int -> ReadS ObjectField
Read, Int -> ObjectField -> String -> String
[ObjectField] -> String -> String
ObjectField -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ObjectField] -> String -> String
$cshowList :: [ObjectField] -> String -> String
show :: ObjectField -> String
$cshow :: ObjectField -> String
showsPrec :: Int -> ObjectField -> String -> String
$cshowsPrec :: Int -> ObjectField -> String -> String
Show)

_ObjectField :: Name
_ObjectField = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ObjectField")

_ObjectField_name :: FieldName
_ObjectField_name = (String -> FieldName
Core.FieldName String
"name")

_ObjectField_value :: FieldName
_ObjectField_value = (String -> FieldName
Core.FieldName String
"value")

data VariablesDefinition = 
  VariablesDefinition {
    VariablesDefinition -> Variable
variablesDefinitionVariable :: Variable,
    VariablesDefinition -> Type
variablesDefinitionType :: Type,
    VariablesDefinition -> Maybe DefaultValue
variablesDefinitionDefaultValue :: (Maybe DefaultValue),
    VariablesDefinition -> Maybe Directives
variablesDefinitionDirectives :: (Maybe Directives)}
  deriving (VariablesDefinition -> VariablesDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: VariablesDefinition -> VariablesDefinition -> Bool
$c/= :: VariablesDefinition -> VariablesDefinition -> Bool
== :: VariablesDefinition -> VariablesDefinition -> Bool
$c== :: VariablesDefinition -> VariablesDefinition -> Bool
Eq, Eq VariablesDefinition
VariablesDefinition -> VariablesDefinition -> Bool
VariablesDefinition -> VariablesDefinition -> Ordering
VariablesDefinition -> VariablesDefinition -> VariablesDefinition
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
min :: VariablesDefinition -> VariablesDefinition -> VariablesDefinition
$cmin :: VariablesDefinition -> VariablesDefinition -> VariablesDefinition
max :: VariablesDefinition -> VariablesDefinition -> VariablesDefinition
$cmax :: VariablesDefinition -> VariablesDefinition -> VariablesDefinition
>= :: VariablesDefinition -> VariablesDefinition -> Bool
$c>= :: VariablesDefinition -> VariablesDefinition -> Bool
> :: VariablesDefinition -> VariablesDefinition -> Bool
$c> :: VariablesDefinition -> VariablesDefinition -> Bool
<= :: VariablesDefinition -> VariablesDefinition -> Bool
$c<= :: VariablesDefinition -> VariablesDefinition -> Bool
< :: VariablesDefinition -> VariablesDefinition -> Bool
$c< :: VariablesDefinition -> VariablesDefinition -> Bool
compare :: VariablesDefinition -> VariablesDefinition -> Ordering
$ccompare :: VariablesDefinition -> VariablesDefinition -> Ordering
Ord, ReadPrec [VariablesDefinition]
ReadPrec VariablesDefinition
Int -> ReadS VariablesDefinition
ReadS [VariablesDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [VariablesDefinition]
$creadListPrec :: ReadPrec [VariablesDefinition]
readPrec :: ReadPrec VariablesDefinition
$creadPrec :: ReadPrec VariablesDefinition
readList :: ReadS [VariablesDefinition]
$creadList :: ReadS [VariablesDefinition]
readsPrec :: Int -> ReadS VariablesDefinition
$creadsPrec :: Int -> ReadS VariablesDefinition
Read, Int -> VariablesDefinition -> String -> String
[VariablesDefinition] -> String -> String
VariablesDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [VariablesDefinition] -> String -> String
$cshowList :: [VariablesDefinition] -> String -> String
show :: VariablesDefinition -> String
$cshow :: VariablesDefinition -> String
showsPrec :: Int -> VariablesDefinition -> String -> String
$cshowsPrec :: Int -> VariablesDefinition -> String -> String
Show)

_VariablesDefinition :: Name
_VariablesDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.VariablesDefinition")

_VariablesDefinition_variable :: FieldName
_VariablesDefinition_variable = (String -> FieldName
Core.FieldName String
"variable")

_VariablesDefinition_type :: FieldName
_VariablesDefinition_type = (String -> FieldName
Core.FieldName String
"type")

_VariablesDefinition_defaultValue :: FieldName
_VariablesDefinition_defaultValue = (String -> FieldName
Core.FieldName String
"defaultValue")

_VariablesDefinition_directives :: FieldName
_VariablesDefinition_directives = (String -> FieldName
Core.FieldName String
"directives")

newtype Variable = 
  Variable {
    Variable -> Name
unVariable :: Name}
  deriving (Variable -> Variable -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Variable -> Variable -> Bool
$c/= :: Variable -> Variable -> Bool
== :: Variable -> Variable -> Bool
$c== :: Variable -> Variable -> Bool
Eq, Eq Variable
Variable -> Variable -> Bool
Variable -> Variable -> Ordering
Variable -> Variable -> Variable
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
min :: Variable -> Variable -> Variable
$cmin :: Variable -> Variable -> Variable
max :: Variable -> Variable -> Variable
$cmax :: Variable -> Variable -> Variable
>= :: Variable -> Variable -> Bool
$c>= :: Variable -> Variable -> Bool
> :: Variable -> Variable -> Bool
$c> :: Variable -> Variable -> Bool
<= :: Variable -> Variable -> Bool
$c<= :: Variable -> Variable -> Bool
< :: Variable -> Variable -> Bool
$c< :: Variable -> Variable -> Bool
compare :: Variable -> Variable -> Ordering
$ccompare :: Variable -> Variable -> Ordering
Ord, ReadPrec [Variable]
ReadPrec Variable
Int -> ReadS Variable
ReadS [Variable]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Variable]
$creadListPrec :: ReadPrec [Variable]
readPrec :: ReadPrec Variable
$creadPrec :: ReadPrec Variable
readList :: ReadS [Variable]
$creadList :: ReadS [Variable]
readsPrec :: Int -> ReadS Variable
$creadsPrec :: Int -> ReadS Variable
Read, Int -> Variable -> String -> String
[Variable] -> String -> String
Variable -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Variable] -> String -> String
$cshowList :: [Variable] -> String -> String
show :: Variable -> String
$cshow :: Variable -> String
showsPrec :: Int -> Variable -> String -> String
$cshowsPrec :: Int -> Variable -> String -> String
Show)

_Variable :: Name
_Variable = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Variable")

data DefaultValue = 
  DefaultValue {
    DefaultValue -> Value
defaultValueValue :: Value}
  deriving (DefaultValue -> DefaultValue -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DefaultValue -> DefaultValue -> Bool
$c/= :: DefaultValue -> DefaultValue -> Bool
== :: DefaultValue -> DefaultValue -> Bool
$c== :: DefaultValue -> DefaultValue -> Bool
Eq, Eq DefaultValue
DefaultValue -> DefaultValue -> Bool
DefaultValue -> DefaultValue -> Ordering
DefaultValue -> DefaultValue -> DefaultValue
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
min :: DefaultValue -> DefaultValue -> DefaultValue
$cmin :: DefaultValue -> DefaultValue -> DefaultValue
max :: DefaultValue -> DefaultValue -> DefaultValue
$cmax :: DefaultValue -> DefaultValue -> DefaultValue
>= :: DefaultValue -> DefaultValue -> Bool
$c>= :: DefaultValue -> DefaultValue -> Bool
> :: DefaultValue -> DefaultValue -> Bool
$c> :: DefaultValue -> DefaultValue -> Bool
<= :: DefaultValue -> DefaultValue -> Bool
$c<= :: DefaultValue -> DefaultValue -> Bool
< :: DefaultValue -> DefaultValue -> Bool
$c< :: DefaultValue -> DefaultValue -> Bool
compare :: DefaultValue -> DefaultValue -> Ordering
$ccompare :: DefaultValue -> DefaultValue -> Ordering
Ord, ReadPrec [DefaultValue]
ReadPrec DefaultValue
Int -> ReadS DefaultValue
ReadS [DefaultValue]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DefaultValue]
$creadListPrec :: ReadPrec [DefaultValue]
readPrec :: ReadPrec DefaultValue
$creadPrec :: ReadPrec DefaultValue
readList :: ReadS [DefaultValue]
$creadList :: ReadS [DefaultValue]
readsPrec :: Int -> ReadS DefaultValue
$creadsPrec :: Int -> ReadS DefaultValue
Read, Int -> DefaultValue -> String -> String
[DefaultValue] -> String -> String
DefaultValue -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DefaultValue] -> String -> String
$cshowList :: [DefaultValue] -> String -> String
show :: DefaultValue -> String
$cshow :: DefaultValue -> String
showsPrec :: Int -> DefaultValue -> String -> String
$cshowsPrec :: Int -> DefaultValue -> String -> String
Show)

_DefaultValue :: Name
_DefaultValue = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.DefaultValue")

_DefaultValue_value :: FieldName
_DefaultValue_value = (String -> FieldName
Core.FieldName String
"value")

data Type = 
  TypeNamed NamedType |
  TypeList ListType |
  TypeNonNull NonNullType
  deriving (Type -> Type -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c== :: Type -> Type -> Bool
Eq, Eq Type
Type -> Type -> Bool
Type -> Type -> Ordering
Type -> Type -> Type
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
min :: Type -> Type -> Type
$cmin :: Type -> Type -> Type
max :: Type -> Type -> Type
$cmax :: Type -> Type -> Type
>= :: Type -> Type -> Bool
$c>= :: Type -> Type -> Bool
> :: Type -> Type -> Bool
$c> :: Type -> Type -> Bool
<= :: Type -> Type -> Bool
$c<= :: Type -> Type -> Bool
< :: Type -> Type -> Bool
$c< :: Type -> Type -> Bool
compare :: Type -> Type -> Ordering
$ccompare :: Type -> Type -> Ordering
Ord, ReadPrec [Type]
ReadPrec Type
Int -> ReadS Type
ReadS [Type]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Type]
$creadListPrec :: ReadPrec [Type]
readPrec :: ReadPrec Type
$creadPrec :: ReadPrec Type
readList :: ReadS [Type]
$creadList :: ReadS [Type]
readsPrec :: Int -> ReadS Type
$creadsPrec :: Int -> ReadS Type
Read, Int -> Type -> String -> String
[Type] -> String -> String
Type -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Type] -> String -> String
$cshowList :: [Type] -> String -> String
show :: Type -> String
$cshow :: Type -> String
showsPrec :: Int -> Type -> String -> String
$cshowsPrec :: Int -> Type -> String -> String
Show)

_Type :: Name
_Type = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Type")

_Type_named :: FieldName
_Type_named = (String -> FieldName
Core.FieldName String
"named")

_Type_list :: FieldName
_Type_list = (String -> FieldName
Core.FieldName String
"list")

_Type_nonNull :: FieldName
_Type_nonNull = (String -> FieldName
Core.FieldName String
"nonNull")

newtype NamedType = 
  NamedType {
    NamedType -> Name
unNamedType :: Name}
  deriving (NamedType -> NamedType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NamedType -> NamedType -> Bool
$c/= :: NamedType -> NamedType -> Bool
== :: NamedType -> NamedType -> Bool
$c== :: NamedType -> NamedType -> Bool
Eq, Eq NamedType
NamedType -> NamedType -> Bool
NamedType -> NamedType -> Ordering
NamedType -> NamedType -> NamedType
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
min :: NamedType -> NamedType -> NamedType
$cmin :: NamedType -> NamedType -> NamedType
max :: NamedType -> NamedType -> NamedType
$cmax :: NamedType -> NamedType -> NamedType
>= :: NamedType -> NamedType -> Bool
$c>= :: NamedType -> NamedType -> Bool
> :: NamedType -> NamedType -> Bool
$c> :: NamedType -> NamedType -> Bool
<= :: NamedType -> NamedType -> Bool
$c<= :: NamedType -> NamedType -> Bool
< :: NamedType -> NamedType -> Bool
$c< :: NamedType -> NamedType -> Bool
compare :: NamedType -> NamedType -> Ordering
$ccompare :: NamedType -> NamedType -> Ordering
Ord, ReadPrec [NamedType]
ReadPrec NamedType
Int -> ReadS NamedType
ReadS [NamedType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NamedType]
$creadListPrec :: ReadPrec [NamedType]
readPrec :: ReadPrec NamedType
$creadPrec :: ReadPrec NamedType
readList :: ReadS [NamedType]
$creadList :: ReadS [NamedType]
readsPrec :: Int -> ReadS NamedType
$creadsPrec :: Int -> ReadS NamedType
Read, Int -> NamedType -> String -> String
[NamedType] -> String -> String
NamedType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [NamedType] -> String -> String
$cshowList :: [NamedType] -> String -> String
show :: NamedType -> String
$cshow :: NamedType -> String
showsPrec :: Int -> NamedType -> String -> String
$cshowsPrec :: Int -> NamedType -> String -> String
Show)

_NamedType :: Name
_NamedType = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.NamedType")

data ListType = 
  ListType {
    ListType -> Type
listTypeType :: Type}
  deriving (ListType -> ListType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ListType -> ListType -> Bool
$c/= :: ListType -> ListType -> Bool
== :: ListType -> ListType -> Bool
$c== :: ListType -> ListType -> Bool
Eq, Eq ListType
ListType -> ListType -> Bool
ListType -> ListType -> Ordering
ListType -> ListType -> ListType
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
min :: ListType -> ListType -> ListType
$cmin :: ListType -> ListType -> ListType
max :: ListType -> ListType -> ListType
$cmax :: ListType -> ListType -> ListType
>= :: ListType -> ListType -> Bool
$c>= :: ListType -> ListType -> Bool
> :: ListType -> ListType -> Bool
$c> :: ListType -> ListType -> Bool
<= :: ListType -> ListType -> Bool
$c<= :: ListType -> ListType -> Bool
< :: ListType -> ListType -> Bool
$c< :: ListType -> ListType -> Bool
compare :: ListType -> ListType -> Ordering
$ccompare :: ListType -> ListType -> Ordering
Ord, ReadPrec [ListType]
ReadPrec ListType
Int -> ReadS ListType
ReadS [ListType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ListType]
$creadListPrec :: ReadPrec [ListType]
readPrec :: ReadPrec ListType
$creadPrec :: ReadPrec ListType
readList :: ReadS [ListType]
$creadList :: ReadS [ListType]
readsPrec :: Int -> ReadS ListType
$creadsPrec :: Int -> ReadS ListType
Read, Int -> ListType -> String -> String
[ListType] -> String -> String
ListType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ListType] -> String -> String
$cshowList :: [ListType] -> String -> String
show :: ListType -> String
$cshow :: ListType -> String
showsPrec :: Int -> ListType -> String -> String
$cshowsPrec :: Int -> ListType -> String -> String
Show)

_ListType :: Name
_ListType = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ListType")

_ListType_type :: FieldName
_ListType_type = (String -> FieldName
Core.FieldName String
"type")

data NonNullType = 
  NonNullTypeNamed NonNullType_Named |
  NonNullTypeList NonNullType_List
  deriving (NonNullType -> NonNullType -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonNullType -> NonNullType -> Bool
$c/= :: NonNullType -> NonNullType -> Bool
== :: NonNullType -> NonNullType -> Bool
$c== :: NonNullType -> NonNullType -> Bool
Eq, Eq NonNullType
NonNullType -> NonNullType -> Bool
NonNullType -> NonNullType -> Ordering
NonNullType -> NonNullType -> NonNullType
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
min :: NonNullType -> NonNullType -> NonNullType
$cmin :: NonNullType -> NonNullType -> NonNullType
max :: NonNullType -> NonNullType -> NonNullType
$cmax :: NonNullType -> NonNullType -> NonNullType
>= :: NonNullType -> NonNullType -> Bool
$c>= :: NonNullType -> NonNullType -> Bool
> :: NonNullType -> NonNullType -> Bool
$c> :: NonNullType -> NonNullType -> Bool
<= :: NonNullType -> NonNullType -> Bool
$c<= :: NonNullType -> NonNullType -> Bool
< :: NonNullType -> NonNullType -> Bool
$c< :: NonNullType -> NonNullType -> Bool
compare :: NonNullType -> NonNullType -> Ordering
$ccompare :: NonNullType -> NonNullType -> Ordering
Ord, ReadPrec [NonNullType]
ReadPrec NonNullType
Int -> ReadS NonNullType
ReadS [NonNullType]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NonNullType]
$creadListPrec :: ReadPrec [NonNullType]
readPrec :: ReadPrec NonNullType
$creadPrec :: ReadPrec NonNullType
readList :: ReadS [NonNullType]
$creadList :: ReadS [NonNullType]
readsPrec :: Int -> ReadS NonNullType
$creadsPrec :: Int -> ReadS NonNullType
Read, Int -> NonNullType -> String -> String
[NonNullType] -> String -> String
NonNullType -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [NonNullType] -> String -> String
$cshowList :: [NonNullType] -> String -> String
show :: NonNullType -> String
$cshow :: NonNullType -> String
showsPrec :: Int -> NonNullType -> String -> String
$cshowsPrec :: Int -> NonNullType -> String -> String
Show)

_NonNullType :: Name
_NonNullType = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.NonNullType")

_NonNullType_named :: FieldName
_NonNullType_named = (String -> FieldName
Core.FieldName String
"named")

_NonNullType_list :: FieldName
_NonNullType_list = (String -> FieldName
Core.FieldName String
"list")

data NonNullType_Named = 
  NonNullType_Named {
    NonNullType_Named -> NamedType
nonNullType_NamedNamedType :: NamedType}
  deriving (NonNullType_Named -> NonNullType_Named -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonNullType_Named -> NonNullType_Named -> Bool
$c/= :: NonNullType_Named -> NonNullType_Named -> Bool
== :: NonNullType_Named -> NonNullType_Named -> Bool
$c== :: NonNullType_Named -> NonNullType_Named -> Bool
Eq, Eq NonNullType_Named
NonNullType_Named -> NonNullType_Named -> Bool
NonNullType_Named -> NonNullType_Named -> Ordering
NonNullType_Named -> NonNullType_Named -> NonNullType_Named
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
min :: NonNullType_Named -> NonNullType_Named -> NonNullType_Named
$cmin :: NonNullType_Named -> NonNullType_Named -> NonNullType_Named
max :: NonNullType_Named -> NonNullType_Named -> NonNullType_Named
$cmax :: NonNullType_Named -> NonNullType_Named -> NonNullType_Named
>= :: NonNullType_Named -> NonNullType_Named -> Bool
$c>= :: NonNullType_Named -> NonNullType_Named -> Bool
> :: NonNullType_Named -> NonNullType_Named -> Bool
$c> :: NonNullType_Named -> NonNullType_Named -> Bool
<= :: NonNullType_Named -> NonNullType_Named -> Bool
$c<= :: NonNullType_Named -> NonNullType_Named -> Bool
< :: NonNullType_Named -> NonNullType_Named -> Bool
$c< :: NonNullType_Named -> NonNullType_Named -> Bool
compare :: NonNullType_Named -> NonNullType_Named -> Ordering
$ccompare :: NonNullType_Named -> NonNullType_Named -> Ordering
Ord, ReadPrec [NonNullType_Named]
ReadPrec NonNullType_Named
Int -> ReadS NonNullType_Named
ReadS [NonNullType_Named]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NonNullType_Named]
$creadListPrec :: ReadPrec [NonNullType_Named]
readPrec :: ReadPrec NonNullType_Named
$creadPrec :: ReadPrec NonNullType_Named
readList :: ReadS [NonNullType_Named]
$creadList :: ReadS [NonNullType_Named]
readsPrec :: Int -> ReadS NonNullType_Named
$creadsPrec :: Int -> ReadS NonNullType_Named
Read, Int -> NonNullType_Named -> String -> String
[NonNullType_Named] -> String -> String
NonNullType_Named -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [NonNullType_Named] -> String -> String
$cshowList :: [NonNullType_Named] -> String -> String
show :: NonNullType_Named -> String
$cshow :: NonNullType_Named -> String
showsPrec :: Int -> NonNullType_Named -> String -> String
$cshowsPrec :: Int -> NonNullType_Named -> String -> String
Show)

_NonNullType_Named :: Name
_NonNullType_Named = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.NonNullType.Named")

_NonNullType_Named_namedType :: FieldName
_NonNullType_Named_namedType = (String -> FieldName
Core.FieldName String
"namedType")

data NonNullType_List = 
  NonNullType_List {
    NonNullType_List -> ListType
nonNullType_ListListType :: ListType}
  deriving (NonNullType_List -> NonNullType_List -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: NonNullType_List -> NonNullType_List -> Bool
$c/= :: NonNullType_List -> NonNullType_List -> Bool
== :: NonNullType_List -> NonNullType_List -> Bool
$c== :: NonNullType_List -> NonNullType_List -> Bool
Eq, Eq NonNullType_List
NonNullType_List -> NonNullType_List -> Bool
NonNullType_List -> NonNullType_List -> Ordering
NonNullType_List -> NonNullType_List -> NonNullType_List
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
min :: NonNullType_List -> NonNullType_List -> NonNullType_List
$cmin :: NonNullType_List -> NonNullType_List -> NonNullType_List
max :: NonNullType_List -> NonNullType_List -> NonNullType_List
$cmax :: NonNullType_List -> NonNullType_List -> NonNullType_List
>= :: NonNullType_List -> NonNullType_List -> Bool
$c>= :: NonNullType_List -> NonNullType_List -> Bool
> :: NonNullType_List -> NonNullType_List -> Bool
$c> :: NonNullType_List -> NonNullType_List -> Bool
<= :: NonNullType_List -> NonNullType_List -> Bool
$c<= :: NonNullType_List -> NonNullType_List -> Bool
< :: NonNullType_List -> NonNullType_List -> Bool
$c< :: NonNullType_List -> NonNullType_List -> Bool
compare :: NonNullType_List -> NonNullType_List -> Ordering
$ccompare :: NonNullType_List -> NonNullType_List -> Ordering
Ord, ReadPrec [NonNullType_List]
ReadPrec NonNullType_List
Int -> ReadS NonNullType_List
ReadS [NonNullType_List]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [NonNullType_List]
$creadListPrec :: ReadPrec [NonNullType_List]
readPrec :: ReadPrec NonNullType_List
$creadPrec :: ReadPrec NonNullType_List
readList :: ReadS [NonNullType_List]
$creadList :: ReadS [NonNullType_List]
readsPrec :: Int -> ReadS NonNullType_List
$creadsPrec :: Int -> ReadS NonNullType_List
Read, Int -> NonNullType_List -> String -> String
[NonNullType_List] -> String -> String
NonNullType_List -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [NonNullType_List] -> String -> String
$cshowList :: [NonNullType_List] -> String -> String
show :: NonNullType_List -> String
$cshow :: NonNullType_List -> String
showsPrec :: Int -> NonNullType_List -> String -> String
$cshowsPrec :: Int -> NonNullType_List -> String -> String
Show)

_NonNullType_List :: Name
_NonNullType_List = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.NonNullType.List")

_NonNullType_List_listType :: FieldName
_NonNullType_List_listType = (String -> FieldName
Core.FieldName String
"listType")

newtype Directives = 
  Directives {
    Directives -> [Directive]
unDirectives :: [Directive]}
  deriving (Directives -> Directives -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Directives -> Directives -> Bool
$c/= :: Directives -> Directives -> Bool
== :: Directives -> Directives -> Bool
$c== :: Directives -> Directives -> Bool
Eq, Eq Directives
Directives -> Directives -> Bool
Directives -> Directives -> Ordering
Directives -> Directives -> Directives
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
min :: Directives -> Directives -> Directives
$cmin :: Directives -> Directives -> Directives
max :: Directives -> Directives -> Directives
$cmax :: Directives -> Directives -> Directives
>= :: Directives -> Directives -> Bool
$c>= :: Directives -> Directives -> Bool
> :: Directives -> Directives -> Bool
$c> :: Directives -> Directives -> Bool
<= :: Directives -> Directives -> Bool
$c<= :: Directives -> Directives -> Bool
< :: Directives -> Directives -> Bool
$c< :: Directives -> Directives -> Bool
compare :: Directives -> Directives -> Ordering
$ccompare :: Directives -> Directives -> Ordering
Ord, ReadPrec [Directives]
ReadPrec Directives
Int -> ReadS Directives
ReadS [Directives]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Directives]
$creadListPrec :: ReadPrec [Directives]
readPrec :: ReadPrec Directives
$creadPrec :: ReadPrec Directives
readList :: ReadS [Directives]
$creadList :: ReadS [Directives]
readsPrec :: Int -> ReadS Directives
$creadsPrec :: Int -> ReadS Directives
Read, Int -> Directives -> String -> String
[Directives] -> String -> String
Directives -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Directives] -> String -> String
$cshowList :: [Directives] -> String -> String
show :: Directives -> String
$cshow :: Directives -> String
showsPrec :: Int -> Directives -> String -> String
$cshowsPrec :: Int -> Directives -> String -> String
Show)

_Directives :: Name
_Directives = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Directives")

data Directive = 
  Directive {
    Directive -> Name
directiveName :: Name,
    Directive -> Maybe Arguments
directiveArguments :: (Maybe Arguments)}
  deriving (Directive -> Directive -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Directive -> Directive -> Bool
$c/= :: Directive -> Directive -> Bool
== :: Directive -> Directive -> Bool
$c== :: Directive -> Directive -> Bool
Eq, Eq Directive
Directive -> Directive -> Bool
Directive -> Directive -> Ordering
Directive -> Directive -> Directive
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
min :: Directive -> Directive -> Directive
$cmin :: Directive -> Directive -> Directive
max :: Directive -> Directive -> Directive
$cmax :: Directive -> Directive -> Directive
>= :: Directive -> Directive -> Bool
$c>= :: Directive -> Directive -> Bool
> :: Directive -> Directive -> Bool
$c> :: Directive -> Directive -> Bool
<= :: Directive -> Directive -> Bool
$c<= :: Directive -> Directive -> Bool
< :: Directive -> Directive -> Bool
$c< :: Directive -> Directive -> Bool
compare :: Directive -> Directive -> Ordering
$ccompare :: Directive -> Directive -> Ordering
Ord, ReadPrec [Directive]
ReadPrec Directive
Int -> ReadS Directive
ReadS [Directive]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Directive]
$creadListPrec :: ReadPrec [Directive]
readPrec :: ReadPrec Directive
$creadPrec :: ReadPrec Directive
readList :: ReadS [Directive]
$creadList :: ReadS [Directive]
readsPrec :: Int -> ReadS Directive
$creadsPrec :: Int -> ReadS Directive
Read, Int -> Directive -> String -> String
[Directive] -> String -> String
Directive -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Directive] -> String -> String
$cshowList :: [Directive] -> String -> String
show :: Directive -> String
$cshow :: Directive -> String
showsPrec :: Int -> Directive -> String -> String
$cshowsPrec :: Int -> Directive -> String -> String
Show)

_Directive :: Name
_Directive = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Directive")

_Directive_name :: FieldName
_Directive_name = (String -> FieldName
Core.FieldName String
"name")

_Directive_arguments :: FieldName
_Directive_arguments = (String -> FieldName
Core.FieldName String
"arguments")

newtype TypeSystemDocment = 
  TypeSystemDocment {
    TypeSystemDocment -> [TypeSystemDefinition]
unTypeSystemDocment :: [TypeSystemDefinition]}
  deriving (TypeSystemDocment -> TypeSystemDocment -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeSystemDocment -> TypeSystemDocment -> Bool
$c/= :: TypeSystemDocment -> TypeSystemDocment -> Bool
== :: TypeSystemDocment -> TypeSystemDocment -> Bool
$c== :: TypeSystemDocment -> TypeSystemDocment -> Bool
Eq, Eq TypeSystemDocment
TypeSystemDocment -> TypeSystemDocment -> Bool
TypeSystemDocment -> TypeSystemDocment -> Ordering
TypeSystemDocment -> TypeSystemDocment -> TypeSystemDocment
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
min :: TypeSystemDocment -> TypeSystemDocment -> TypeSystemDocment
$cmin :: TypeSystemDocment -> TypeSystemDocment -> TypeSystemDocment
max :: TypeSystemDocment -> TypeSystemDocment -> TypeSystemDocment
$cmax :: TypeSystemDocment -> TypeSystemDocment -> TypeSystemDocment
>= :: TypeSystemDocment -> TypeSystemDocment -> Bool
$c>= :: TypeSystemDocment -> TypeSystemDocment -> Bool
> :: TypeSystemDocment -> TypeSystemDocment -> Bool
$c> :: TypeSystemDocment -> TypeSystemDocment -> Bool
<= :: TypeSystemDocment -> TypeSystemDocment -> Bool
$c<= :: TypeSystemDocment -> TypeSystemDocment -> Bool
< :: TypeSystemDocment -> TypeSystemDocment -> Bool
$c< :: TypeSystemDocment -> TypeSystemDocment -> Bool
compare :: TypeSystemDocment -> TypeSystemDocment -> Ordering
$ccompare :: TypeSystemDocment -> TypeSystemDocment -> Ordering
Ord, ReadPrec [TypeSystemDocment]
ReadPrec TypeSystemDocment
Int -> ReadS TypeSystemDocment
ReadS [TypeSystemDocment]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeSystemDocment]
$creadListPrec :: ReadPrec [TypeSystemDocment]
readPrec :: ReadPrec TypeSystemDocment
$creadPrec :: ReadPrec TypeSystemDocment
readList :: ReadS [TypeSystemDocment]
$creadList :: ReadS [TypeSystemDocment]
readsPrec :: Int -> ReadS TypeSystemDocment
$creadsPrec :: Int -> ReadS TypeSystemDocment
Read, Int -> TypeSystemDocment -> String -> String
[TypeSystemDocment] -> String -> String
TypeSystemDocment -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeSystemDocment] -> String -> String
$cshowList :: [TypeSystemDocment] -> String -> String
show :: TypeSystemDocment -> String
$cshow :: TypeSystemDocment -> String
showsPrec :: Int -> TypeSystemDocment -> String -> String
$cshowsPrec :: Int -> TypeSystemDocment -> String -> String
Show)

_TypeSystemDocment :: Name
_TypeSystemDocment = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.TypeSystemDocment")

data TypeSystemDefinition = 
  TypeSystemDefinitionSchema SchemaDefinition |
  TypeSystemDefinitionType TypeDefinition |
  TypeSystemDefinitionDirective DirectiveDefinition
  deriving (TypeSystemDefinition -> TypeSystemDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
$c/= :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
== :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
$c== :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
Eq, Eq TypeSystemDefinition
TypeSystemDefinition -> TypeSystemDefinition -> Bool
TypeSystemDefinition -> TypeSystemDefinition -> Ordering
TypeSystemDefinition
-> TypeSystemDefinition -> TypeSystemDefinition
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
min :: TypeSystemDefinition
-> TypeSystemDefinition -> TypeSystemDefinition
$cmin :: TypeSystemDefinition
-> TypeSystemDefinition -> TypeSystemDefinition
max :: TypeSystemDefinition
-> TypeSystemDefinition -> TypeSystemDefinition
$cmax :: TypeSystemDefinition
-> TypeSystemDefinition -> TypeSystemDefinition
>= :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
$c>= :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
> :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
$c> :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
<= :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
$c<= :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
< :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
$c< :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
compare :: TypeSystemDefinition -> TypeSystemDefinition -> Ordering
$ccompare :: TypeSystemDefinition -> TypeSystemDefinition -> Ordering
Ord, ReadPrec [TypeSystemDefinition]
ReadPrec TypeSystemDefinition
Int -> ReadS TypeSystemDefinition
ReadS [TypeSystemDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeSystemDefinition]
$creadListPrec :: ReadPrec [TypeSystemDefinition]
readPrec :: ReadPrec TypeSystemDefinition
$creadPrec :: ReadPrec TypeSystemDefinition
readList :: ReadS [TypeSystemDefinition]
$creadList :: ReadS [TypeSystemDefinition]
readsPrec :: Int -> ReadS TypeSystemDefinition
$creadsPrec :: Int -> ReadS TypeSystemDefinition
Read, Int -> TypeSystemDefinition -> String -> String
[TypeSystemDefinition] -> String -> String
TypeSystemDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeSystemDefinition] -> String -> String
$cshowList :: [TypeSystemDefinition] -> String -> String
show :: TypeSystemDefinition -> String
$cshow :: TypeSystemDefinition -> String
showsPrec :: Int -> TypeSystemDefinition -> String -> String
$cshowsPrec :: Int -> TypeSystemDefinition -> String -> String
Show)

_TypeSystemDefinition :: Name
_TypeSystemDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.TypeSystemDefinition")

_TypeSystemDefinition_schema :: FieldName
_TypeSystemDefinition_schema = (String -> FieldName
Core.FieldName String
"schema")

_TypeSystemDefinition_type :: FieldName
_TypeSystemDefinition_type = (String -> FieldName
Core.FieldName String
"type")

_TypeSystemDefinition_directive :: FieldName
_TypeSystemDefinition_directive = (String -> FieldName
Core.FieldName String
"directive")

newtype TypeSystemExtensionDocument = 
  TypeSystemExtensionDocument {
    TypeSystemExtensionDocument -> [TypeSystemDefinitionOrExtension]
unTypeSystemExtensionDocument :: [TypeSystemDefinitionOrExtension]}
  deriving (TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
$c/= :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
== :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
$c== :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
Eq, Eq TypeSystemExtensionDocument
TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> Ordering
TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> TypeSystemExtensionDocument
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
min :: TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> TypeSystemExtensionDocument
$cmin :: TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> TypeSystemExtensionDocument
max :: TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> TypeSystemExtensionDocument
$cmax :: TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> TypeSystemExtensionDocument
>= :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
$c>= :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
> :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
$c> :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
<= :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
$c<= :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
< :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
$c< :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
compare :: TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> Ordering
$ccompare :: TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> Ordering
Ord, ReadPrec [TypeSystemExtensionDocument]
ReadPrec TypeSystemExtensionDocument
Int -> ReadS TypeSystemExtensionDocument
ReadS [TypeSystemExtensionDocument]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeSystemExtensionDocument]
$creadListPrec :: ReadPrec [TypeSystemExtensionDocument]
readPrec :: ReadPrec TypeSystemExtensionDocument
$creadPrec :: ReadPrec TypeSystemExtensionDocument
readList :: ReadS [TypeSystemExtensionDocument]
$creadList :: ReadS [TypeSystemExtensionDocument]
readsPrec :: Int -> ReadS TypeSystemExtensionDocument
$creadsPrec :: Int -> ReadS TypeSystemExtensionDocument
Read, Int -> TypeSystemExtensionDocument -> String -> String
[TypeSystemExtensionDocument] -> String -> String
TypeSystemExtensionDocument -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeSystemExtensionDocument] -> String -> String
$cshowList :: [TypeSystemExtensionDocument] -> String -> String
show :: TypeSystemExtensionDocument -> String
$cshow :: TypeSystemExtensionDocument -> String
showsPrec :: Int -> TypeSystemExtensionDocument -> String -> String
$cshowsPrec :: Int -> TypeSystemExtensionDocument -> String -> String
Show)

_TypeSystemExtensionDocument :: Name
_TypeSystemExtensionDocument = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.TypeSystemExtensionDocument")

data TypeSystemDefinitionOrExtension = 
  TypeSystemDefinitionOrExtensionDefinition TypeSystemDefinition |
  TypeSystemDefinitionOrExtensionExtension TypeSystemExtension
  deriving (TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
$c/= :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
== :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
$c== :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
Eq, Eq TypeSystemDefinitionOrExtension
TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Ordering
TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
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
min :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
$cmin :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
max :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
$cmax :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
>= :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
$c>= :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
> :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
$c> :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
<= :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
$c<= :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
< :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
$c< :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
compare :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Ordering
$ccompare :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Ordering
Ord, ReadPrec [TypeSystemDefinitionOrExtension]
ReadPrec TypeSystemDefinitionOrExtension
Int -> ReadS TypeSystemDefinitionOrExtension
ReadS [TypeSystemDefinitionOrExtension]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeSystemDefinitionOrExtension]
$creadListPrec :: ReadPrec [TypeSystemDefinitionOrExtension]
readPrec :: ReadPrec TypeSystemDefinitionOrExtension
$creadPrec :: ReadPrec TypeSystemDefinitionOrExtension
readList :: ReadS [TypeSystemDefinitionOrExtension]
$creadList :: ReadS [TypeSystemDefinitionOrExtension]
readsPrec :: Int -> ReadS TypeSystemDefinitionOrExtension
$creadsPrec :: Int -> ReadS TypeSystemDefinitionOrExtension
Read, Int -> TypeSystemDefinitionOrExtension -> String -> String
[TypeSystemDefinitionOrExtension] -> String -> String
TypeSystemDefinitionOrExtension -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeSystemDefinitionOrExtension] -> String -> String
$cshowList :: [TypeSystemDefinitionOrExtension] -> String -> String
show :: TypeSystemDefinitionOrExtension -> String
$cshow :: TypeSystemDefinitionOrExtension -> String
showsPrec :: Int -> TypeSystemDefinitionOrExtension -> String -> String
$cshowsPrec :: Int -> TypeSystemDefinitionOrExtension -> String -> String
Show)

_TypeSystemDefinitionOrExtension :: Name
_TypeSystemDefinitionOrExtension = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.TypeSystemDefinitionOrExtension")

_TypeSystemDefinitionOrExtension_definition :: FieldName
_TypeSystemDefinitionOrExtension_definition = (String -> FieldName
Core.FieldName String
"definition")

_TypeSystemDefinitionOrExtension_extension :: FieldName
_TypeSystemDefinitionOrExtension_extension = (String -> FieldName
Core.FieldName String
"extension")

data TypeSystemExtension = 
  TypeSystemExtensionSchema SchemaExtension |
  TypeSystemExtensionType TypeExtension
  deriving (TypeSystemExtension -> TypeSystemExtension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeSystemExtension -> TypeSystemExtension -> Bool
$c/= :: TypeSystemExtension -> TypeSystemExtension -> Bool
== :: TypeSystemExtension -> TypeSystemExtension -> Bool
$c== :: TypeSystemExtension -> TypeSystemExtension -> Bool
Eq, Eq TypeSystemExtension
TypeSystemExtension -> TypeSystemExtension -> Bool
TypeSystemExtension -> TypeSystemExtension -> Ordering
TypeSystemExtension -> TypeSystemExtension -> TypeSystemExtension
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
min :: TypeSystemExtension -> TypeSystemExtension -> TypeSystemExtension
$cmin :: TypeSystemExtension -> TypeSystemExtension -> TypeSystemExtension
max :: TypeSystemExtension -> TypeSystemExtension -> TypeSystemExtension
$cmax :: TypeSystemExtension -> TypeSystemExtension -> TypeSystemExtension
>= :: TypeSystemExtension -> TypeSystemExtension -> Bool
$c>= :: TypeSystemExtension -> TypeSystemExtension -> Bool
> :: TypeSystemExtension -> TypeSystemExtension -> Bool
$c> :: TypeSystemExtension -> TypeSystemExtension -> Bool
<= :: TypeSystemExtension -> TypeSystemExtension -> Bool
$c<= :: TypeSystemExtension -> TypeSystemExtension -> Bool
< :: TypeSystemExtension -> TypeSystemExtension -> Bool
$c< :: TypeSystemExtension -> TypeSystemExtension -> Bool
compare :: TypeSystemExtension -> TypeSystemExtension -> Ordering
$ccompare :: TypeSystemExtension -> TypeSystemExtension -> Ordering
Ord, ReadPrec [TypeSystemExtension]
ReadPrec TypeSystemExtension
Int -> ReadS TypeSystemExtension
ReadS [TypeSystemExtension]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeSystemExtension]
$creadListPrec :: ReadPrec [TypeSystemExtension]
readPrec :: ReadPrec TypeSystemExtension
$creadPrec :: ReadPrec TypeSystemExtension
readList :: ReadS [TypeSystemExtension]
$creadList :: ReadS [TypeSystemExtension]
readsPrec :: Int -> ReadS TypeSystemExtension
$creadsPrec :: Int -> ReadS TypeSystemExtension
Read, Int -> TypeSystemExtension -> String -> String
[TypeSystemExtension] -> String -> String
TypeSystemExtension -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeSystemExtension] -> String -> String
$cshowList :: [TypeSystemExtension] -> String -> String
show :: TypeSystemExtension -> String
$cshow :: TypeSystemExtension -> String
showsPrec :: Int -> TypeSystemExtension -> String -> String
$cshowsPrec :: Int -> TypeSystemExtension -> String -> String
Show)

_TypeSystemExtension :: Name
_TypeSystemExtension = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.TypeSystemExtension")

_TypeSystemExtension_schema :: FieldName
_TypeSystemExtension_schema = (String -> FieldName
Core.FieldName String
"schema")

_TypeSystemExtension_type :: FieldName
_TypeSystemExtension_type = (String -> FieldName
Core.FieldName String
"type")

data SchemaDefinition = 
  SchemaDefinition {
    SchemaDefinition -> Maybe Description
schemaDefinitionDescription :: (Maybe Description),
    SchemaDefinition -> Maybe Directives
schemaDefinitionDirectives :: (Maybe Directives),
    SchemaDefinition -> RootOperationTypeDefinition
schemaDefinitionRootOperationTypeDefinition :: RootOperationTypeDefinition}
  deriving (SchemaDefinition -> SchemaDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SchemaDefinition -> SchemaDefinition -> Bool
$c/= :: SchemaDefinition -> SchemaDefinition -> Bool
== :: SchemaDefinition -> SchemaDefinition -> Bool
$c== :: SchemaDefinition -> SchemaDefinition -> Bool
Eq, Eq SchemaDefinition
SchemaDefinition -> SchemaDefinition -> Bool
SchemaDefinition -> SchemaDefinition -> Ordering
SchemaDefinition -> SchemaDefinition -> SchemaDefinition
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
min :: SchemaDefinition -> SchemaDefinition -> SchemaDefinition
$cmin :: SchemaDefinition -> SchemaDefinition -> SchemaDefinition
max :: SchemaDefinition -> SchemaDefinition -> SchemaDefinition
$cmax :: SchemaDefinition -> SchemaDefinition -> SchemaDefinition
>= :: SchemaDefinition -> SchemaDefinition -> Bool
$c>= :: SchemaDefinition -> SchemaDefinition -> Bool
> :: SchemaDefinition -> SchemaDefinition -> Bool
$c> :: SchemaDefinition -> SchemaDefinition -> Bool
<= :: SchemaDefinition -> SchemaDefinition -> Bool
$c<= :: SchemaDefinition -> SchemaDefinition -> Bool
< :: SchemaDefinition -> SchemaDefinition -> Bool
$c< :: SchemaDefinition -> SchemaDefinition -> Bool
compare :: SchemaDefinition -> SchemaDefinition -> Ordering
$ccompare :: SchemaDefinition -> SchemaDefinition -> Ordering
Ord, ReadPrec [SchemaDefinition]
ReadPrec SchemaDefinition
Int -> ReadS SchemaDefinition
ReadS [SchemaDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SchemaDefinition]
$creadListPrec :: ReadPrec [SchemaDefinition]
readPrec :: ReadPrec SchemaDefinition
$creadPrec :: ReadPrec SchemaDefinition
readList :: ReadS [SchemaDefinition]
$creadList :: ReadS [SchemaDefinition]
readsPrec :: Int -> ReadS SchemaDefinition
$creadsPrec :: Int -> ReadS SchemaDefinition
Read, Int -> SchemaDefinition -> String -> String
[SchemaDefinition] -> String -> String
SchemaDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SchemaDefinition] -> String -> String
$cshowList :: [SchemaDefinition] -> String -> String
show :: SchemaDefinition -> String
$cshow :: SchemaDefinition -> String
showsPrec :: Int -> SchemaDefinition -> String -> String
$cshowsPrec :: Int -> SchemaDefinition -> String -> String
Show)

_SchemaDefinition :: Name
_SchemaDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.SchemaDefinition")

_SchemaDefinition_description :: FieldName
_SchemaDefinition_description = (String -> FieldName
Core.FieldName String
"description")

_SchemaDefinition_directives :: FieldName
_SchemaDefinition_directives = (String -> FieldName
Core.FieldName String
"directives")

_SchemaDefinition_rootOperationTypeDefinition :: FieldName
_SchemaDefinition_rootOperationTypeDefinition = (String -> FieldName
Core.FieldName String
"rootOperationTypeDefinition")

data SchemaExtension = 
  SchemaExtensionSequence SchemaExtension_Sequence |
  SchemaExtensionSequence2 SchemaExtension_Sequence2
  deriving (SchemaExtension -> SchemaExtension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SchemaExtension -> SchemaExtension -> Bool
$c/= :: SchemaExtension -> SchemaExtension -> Bool
== :: SchemaExtension -> SchemaExtension -> Bool
$c== :: SchemaExtension -> SchemaExtension -> Bool
Eq, Eq SchemaExtension
SchemaExtension -> SchemaExtension -> Bool
SchemaExtension -> SchemaExtension -> Ordering
SchemaExtension -> SchemaExtension -> SchemaExtension
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
min :: SchemaExtension -> SchemaExtension -> SchemaExtension
$cmin :: SchemaExtension -> SchemaExtension -> SchemaExtension
max :: SchemaExtension -> SchemaExtension -> SchemaExtension
$cmax :: SchemaExtension -> SchemaExtension -> SchemaExtension
>= :: SchemaExtension -> SchemaExtension -> Bool
$c>= :: SchemaExtension -> SchemaExtension -> Bool
> :: SchemaExtension -> SchemaExtension -> Bool
$c> :: SchemaExtension -> SchemaExtension -> Bool
<= :: SchemaExtension -> SchemaExtension -> Bool
$c<= :: SchemaExtension -> SchemaExtension -> Bool
< :: SchemaExtension -> SchemaExtension -> Bool
$c< :: SchemaExtension -> SchemaExtension -> Bool
compare :: SchemaExtension -> SchemaExtension -> Ordering
$ccompare :: SchemaExtension -> SchemaExtension -> Ordering
Ord, ReadPrec [SchemaExtension]
ReadPrec SchemaExtension
Int -> ReadS SchemaExtension
ReadS [SchemaExtension]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SchemaExtension]
$creadListPrec :: ReadPrec [SchemaExtension]
readPrec :: ReadPrec SchemaExtension
$creadPrec :: ReadPrec SchemaExtension
readList :: ReadS [SchemaExtension]
$creadList :: ReadS [SchemaExtension]
readsPrec :: Int -> ReadS SchemaExtension
$creadsPrec :: Int -> ReadS SchemaExtension
Read, Int -> SchemaExtension -> String -> String
[SchemaExtension] -> String -> String
SchemaExtension -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SchemaExtension] -> String -> String
$cshowList :: [SchemaExtension] -> String -> String
show :: SchemaExtension -> String
$cshow :: SchemaExtension -> String
showsPrec :: Int -> SchemaExtension -> String -> String
$cshowsPrec :: Int -> SchemaExtension -> String -> String
Show)

_SchemaExtension :: Name
_SchemaExtension = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.SchemaExtension")

_SchemaExtension_sequence :: FieldName
_SchemaExtension_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_SchemaExtension_sequence2 :: FieldName
_SchemaExtension_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data SchemaExtension_Sequence = 
  SchemaExtension_Sequence {
    SchemaExtension_Sequence -> Maybe Directives
schemaExtension_SequenceDirectives :: (Maybe Directives),
    SchemaExtension_Sequence -> RootOperationTypeDefinition
schemaExtension_SequenceRootOperationTypeDefinition :: RootOperationTypeDefinition}
  deriving (SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
$c/= :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
== :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
$c== :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
Eq, Eq SchemaExtension_Sequence
SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
SchemaExtension_Sequence -> SchemaExtension_Sequence -> Ordering
SchemaExtension_Sequence
-> SchemaExtension_Sequence -> SchemaExtension_Sequence
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
min :: SchemaExtension_Sequence
-> SchemaExtension_Sequence -> SchemaExtension_Sequence
$cmin :: SchemaExtension_Sequence
-> SchemaExtension_Sequence -> SchemaExtension_Sequence
max :: SchemaExtension_Sequence
-> SchemaExtension_Sequence -> SchemaExtension_Sequence
$cmax :: SchemaExtension_Sequence
-> SchemaExtension_Sequence -> SchemaExtension_Sequence
>= :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
$c>= :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
> :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
$c> :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
<= :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
$c<= :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
< :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
$c< :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
compare :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Ordering
$ccompare :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Ordering
Ord, ReadPrec [SchemaExtension_Sequence]
ReadPrec SchemaExtension_Sequence
Int -> ReadS SchemaExtension_Sequence
ReadS [SchemaExtension_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SchemaExtension_Sequence]
$creadListPrec :: ReadPrec [SchemaExtension_Sequence]
readPrec :: ReadPrec SchemaExtension_Sequence
$creadPrec :: ReadPrec SchemaExtension_Sequence
readList :: ReadS [SchemaExtension_Sequence]
$creadList :: ReadS [SchemaExtension_Sequence]
readsPrec :: Int -> ReadS SchemaExtension_Sequence
$creadsPrec :: Int -> ReadS SchemaExtension_Sequence
Read, Int -> SchemaExtension_Sequence -> String -> String
[SchemaExtension_Sequence] -> String -> String
SchemaExtension_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SchemaExtension_Sequence] -> String -> String
$cshowList :: [SchemaExtension_Sequence] -> String -> String
show :: SchemaExtension_Sequence -> String
$cshow :: SchemaExtension_Sequence -> String
showsPrec :: Int -> SchemaExtension_Sequence -> String -> String
$cshowsPrec :: Int -> SchemaExtension_Sequence -> String -> String
Show)

_SchemaExtension_Sequence :: Name
_SchemaExtension_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.SchemaExtension.Sequence")

_SchemaExtension_Sequence_directives :: FieldName
_SchemaExtension_Sequence_directives = (String -> FieldName
Core.FieldName String
"directives")

_SchemaExtension_Sequence_rootOperationTypeDefinition :: FieldName
_SchemaExtension_Sequence_rootOperationTypeDefinition = (String -> FieldName
Core.FieldName String
"rootOperationTypeDefinition")

data SchemaExtension_Sequence2 = 
  SchemaExtension_Sequence2 {
    SchemaExtension_Sequence2 -> Directives
schemaExtension_Sequence2Directives :: Directives}
  deriving (SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
$c/= :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
== :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
$c== :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
Eq, Eq SchemaExtension_Sequence2
SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Ordering
SchemaExtension_Sequence2
-> SchemaExtension_Sequence2 -> SchemaExtension_Sequence2
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
min :: SchemaExtension_Sequence2
-> SchemaExtension_Sequence2 -> SchemaExtension_Sequence2
$cmin :: SchemaExtension_Sequence2
-> SchemaExtension_Sequence2 -> SchemaExtension_Sequence2
max :: SchemaExtension_Sequence2
-> SchemaExtension_Sequence2 -> SchemaExtension_Sequence2
$cmax :: SchemaExtension_Sequence2
-> SchemaExtension_Sequence2 -> SchemaExtension_Sequence2
>= :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
$c>= :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
> :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
$c> :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
<= :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
$c<= :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
< :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
$c< :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Bool
compare :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Ordering
$ccompare :: SchemaExtension_Sequence2 -> SchemaExtension_Sequence2 -> Ordering
Ord, ReadPrec [SchemaExtension_Sequence2]
ReadPrec SchemaExtension_Sequence2
Int -> ReadS SchemaExtension_Sequence2
ReadS [SchemaExtension_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [SchemaExtension_Sequence2]
$creadListPrec :: ReadPrec [SchemaExtension_Sequence2]
readPrec :: ReadPrec SchemaExtension_Sequence2
$creadPrec :: ReadPrec SchemaExtension_Sequence2
readList :: ReadS [SchemaExtension_Sequence2]
$creadList :: ReadS [SchemaExtension_Sequence2]
readsPrec :: Int -> ReadS SchemaExtension_Sequence2
$creadsPrec :: Int -> ReadS SchemaExtension_Sequence2
Read, Int -> SchemaExtension_Sequence2 -> String -> String
[SchemaExtension_Sequence2] -> String -> String
SchemaExtension_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [SchemaExtension_Sequence2] -> String -> String
$cshowList :: [SchemaExtension_Sequence2] -> String -> String
show :: SchemaExtension_Sequence2 -> String
$cshow :: SchemaExtension_Sequence2 -> String
showsPrec :: Int -> SchemaExtension_Sequence2 -> String -> String
$cshowsPrec :: Int -> SchemaExtension_Sequence2 -> String -> String
Show)

_SchemaExtension_Sequence2 :: Name
_SchemaExtension_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.SchemaExtension.Sequence2")

_SchemaExtension_Sequence2_directives :: FieldName
_SchemaExtension_Sequence2_directives = (String -> FieldName
Core.FieldName String
"directives")

data RootOperationTypeDefinition = 
  RootOperationTypeDefinition {
    RootOperationTypeDefinition -> OperationType
rootOperationTypeDefinitionOperationType :: OperationType,
    RootOperationTypeDefinition -> NamedType
rootOperationTypeDefinitionNamedType :: NamedType}
  deriving (RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
$c/= :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
== :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
$c== :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
Eq, Eq RootOperationTypeDefinition
RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
RootOperationTypeDefinition
-> RootOperationTypeDefinition -> Ordering
RootOperationTypeDefinition
-> RootOperationTypeDefinition -> RootOperationTypeDefinition
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
min :: RootOperationTypeDefinition
-> RootOperationTypeDefinition -> RootOperationTypeDefinition
$cmin :: RootOperationTypeDefinition
-> RootOperationTypeDefinition -> RootOperationTypeDefinition
max :: RootOperationTypeDefinition
-> RootOperationTypeDefinition -> RootOperationTypeDefinition
$cmax :: RootOperationTypeDefinition
-> RootOperationTypeDefinition -> RootOperationTypeDefinition
>= :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
$c>= :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
> :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
$c> :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
<= :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
$c<= :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
< :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
$c< :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
compare :: RootOperationTypeDefinition
-> RootOperationTypeDefinition -> Ordering
$ccompare :: RootOperationTypeDefinition
-> RootOperationTypeDefinition -> Ordering
Ord, ReadPrec [RootOperationTypeDefinition]
ReadPrec RootOperationTypeDefinition
Int -> ReadS RootOperationTypeDefinition
ReadS [RootOperationTypeDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [RootOperationTypeDefinition]
$creadListPrec :: ReadPrec [RootOperationTypeDefinition]
readPrec :: ReadPrec RootOperationTypeDefinition
$creadPrec :: ReadPrec RootOperationTypeDefinition
readList :: ReadS [RootOperationTypeDefinition]
$creadList :: ReadS [RootOperationTypeDefinition]
readsPrec :: Int -> ReadS RootOperationTypeDefinition
$creadsPrec :: Int -> ReadS RootOperationTypeDefinition
Read, Int -> RootOperationTypeDefinition -> String -> String
[RootOperationTypeDefinition] -> String -> String
RootOperationTypeDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [RootOperationTypeDefinition] -> String -> String
$cshowList :: [RootOperationTypeDefinition] -> String -> String
show :: RootOperationTypeDefinition -> String
$cshow :: RootOperationTypeDefinition -> String
showsPrec :: Int -> RootOperationTypeDefinition -> String -> String
$cshowsPrec :: Int -> RootOperationTypeDefinition -> String -> String
Show)

_RootOperationTypeDefinition :: Name
_RootOperationTypeDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.RootOperationTypeDefinition")

_RootOperationTypeDefinition_operationType :: FieldName
_RootOperationTypeDefinition_operationType = (String -> FieldName
Core.FieldName String
"operationType")

_RootOperationTypeDefinition_namedType :: FieldName
_RootOperationTypeDefinition_namedType = (String -> FieldName
Core.FieldName String
"namedType")

newtype Description = 
  Description {
    Description -> StringValue
unDescription :: StringValue}
  deriving (Description -> Description -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Description -> Description -> Bool
$c/= :: Description -> Description -> Bool
== :: Description -> Description -> Bool
$c== :: Description -> Description -> Bool
Eq, Eq Description
Description -> Description -> Bool
Description -> Description -> Ordering
Description -> Description -> Description
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
min :: Description -> Description -> Description
$cmin :: Description -> Description -> Description
max :: Description -> Description -> Description
$cmax :: Description -> Description -> Description
>= :: Description -> Description -> Bool
$c>= :: Description -> Description -> Bool
> :: Description -> Description -> Bool
$c> :: Description -> Description -> Bool
<= :: Description -> Description -> Bool
$c<= :: Description -> Description -> Bool
< :: Description -> Description -> Bool
$c< :: Description -> Description -> Bool
compare :: Description -> Description -> Ordering
$ccompare :: Description -> Description -> Ordering
Ord, ReadPrec [Description]
ReadPrec Description
Int -> ReadS Description
ReadS [Description]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Description]
$creadListPrec :: ReadPrec [Description]
readPrec :: ReadPrec Description
$creadPrec :: ReadPrec Description
readList :: ReadS [Description]
$creadList :: ReadS [Description]
readsPrec :: Int -> ReadS Description
$creadsPrec :: Int -> ReadS Description
Read, Int -> Description -> String -> String
[Description] -> String -> String
Description -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [Description] -> String -> String
$cshowList :: [Description] -> String -> String
show :: Description -> String
$cshow :: Description -> String
showsPrec :: Int -> Description -> String -> String
$cshowsPrec :: Int -> Description -> String -> String
Show)

_Description :: Name
_Description = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.Description")

data TypeDefinition = 
  TypeDefinitionScalar ScalarTypeDefinition |
  TypeDefinitionObject ObjectTypeDefinition |
  TypeDefinitionInterface InterfaceTypeDefinition |
  TypeDefinitionUnion UnionTypeDefinition |
  TypeDefinitionEnum EnumTypeDefinition |
  TypeDefinitionInputObject InputObjectTypeDefinition
  deriving (TypeDefinition -> TypeDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeDefinition -> TypeDefinition -> Bool
$c/= :: TypeDefinition -> TypeDefinition -> Bool
== :: TypeDefinition -> TypeDefinition -> Bool
$c== :: TypeDefinition -> TypeDefinition -> Bool
Eq, Eq TypeDefinition
TypeDefinition -> TypeDefinition -> Bool
TypeDefinition -> TypeDefinition -> Ordering
TypeDefinition -> TypeDefinition -> TypeDefinition
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
min :: TypeDefinition -> TypeDefinition -> TypeDefinition
$cmin :: TypeDefinition -> TypeDefinition -> TypeDefinition
max :: TypeDefinition -> TypeDefinition -> TypeDefinition
$cmax :: TypeDefinition -> TypeDefinition -> TypeDefinition
>= :: TypeDefinition -> TypeDefinition -> Bool
$c>= :: TypeDefinition -> TypeDefinition -> Bool
> :: TypeDefinition -> TypeDefinition -> Bool
$c> :: TypeDefinition -> TypeDefinition -> Bool
<= :: TypeDefinition -> TypeDefinition -> Bool
$c<= :: TypeDefinition -> TypeDefinition -> Bool
< :: TypeDefinition -> TypeDefinition -> Bool
$c< :: TypeDefinition -> TypeDefinition -> Bool
compare :: TypeDefinition -> TypeDefinition -> Ordering
$ccompare :: TypeDefinition -> TypeDefinition -> Ordering
Ord, ReadPrec [TypeDefinition]
ReadPrec TypeDefinition
Int -> ReadS TypeDefinition
ReadS [TypeDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeDefinition]
$creadListPrec :: ReadPrec [TypeDefinition]
readPrec :: ReadPrec TypeDefinition
$creadPrec :: ReadPrec TypeDefinition
readList :: ReadS [TypeDefinition]
$creadList :: ReadS [TypeDefinition]
readsPrec :: Int -> ReadS TypeDefinition
$creadsPrec :: Int -> ReadS TypeDefinition
Read, Int -> TypeDefinition -> String -> String
[TypeDefinition] -> String -> String
TypeDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeDefinition] -> String -> String
$cshowList :: [TypeDefinition] -> String -> String
show :: TypeDefinition -> String
$cshow :: TypeDefinition -> String
showsPrec :: Int -> TypeDefinition -> String -> String
$cshowsPrec :: Int -> TypeDefinition -> String -> String
Show)

_TypeDefinition :: Name
_TypeDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.TypeDefinition")

_TypeDefinition_scalar :: FieldName
_TypeDefinition_scalar = (String -> FieldName
Core.FieldName String
"scalar")

_TypeDefinition_object :: FieldName
_TypeDefinition_object = (String -> FieldName
Core.FieldName String
"object")

_TypeDefinition_interface :: FieldName
_TypeDefinition_interface = (String -> FieldName
Core.FieldName String
"interface")

_TypeDefinition_union :: FieldName
_TypeDefinition_union = (String -> FieldName
Core.FieldName String
"union")

_TypeDefinition_enum :: FieldName
_TypeDefinition_enum = (String -> FieldName
Core.FieldName String
"enum")

_TypeDefinition_inputObject :: FieldName
_TypeDefinition_inputObject = (String -> FieldName
Core.FieldName String
"inputObject")

data TypeExtension = 
  TypeExtensionScalar ScalarTypeExtension |
  TypeExtensionObject ObjectTypeExtension |
  TypeExtensionInterface InterfaceTypeExtension |
  TypeExtensionUnion UnionTypeExtension |
  TypeExtensionEnum EnumTypeExtension |
  TypeExtensionInputObject InputObjectTypeExtension
  deriving (TypeExtension -> TypeExtension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: TypeExtension -> TypeExtension -> Bool
$c/= :: TypeExtension -> TypeExtension -> Bool
== :: TypeExtension -> TypeExtension -> Bool
$c== :: TypeExtension -> TypeExtension -> Bool
Eq, Eq TypeExtension
TypeExtension -> TypeExtension -> Bool
TypeExtension -> TypeExtension -> Ordering
TypeExtension -> TypeExtension -> TypeExtension
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
min :: TypeExtension -> TypeExtension -> TypeExtension
$cmin :: TypeExtension -> TypeExtension -> TypeExtension
max :: TypeExtension -> TypeExtension -> TypeExtension
$cmax :: TypeExtension -> TypeExtension -> TypeExtension
>= :: TypeExtension -> TypeExtension -> Bool
$c>= :: TypeExtension -> TypeExtension -> Bool
> :: TypeExtension -> TypeExtension -> Bool
$c> :: TypeExtension -> TypeExtension -> Bool
<= :: TypeExtension -> TypeExtension -> Bool
$c<= :: TypeExtension -> TypeExtension -> Bool
< :: TypeExtension -> TypeExtension -> Bool
$c< :: TypeExtension -> TypeExtension -> Bool
compare :: TypeExtension -> TypeExtension -> Ordering
$ccompare :: TypeExtension -> TypeExtension -> Ordering
Ord, ReadPrec [TypeExtension]
ReadPrec TypeExtension
Int -> ReadS TypeExtension
ReadS [TypeExtension]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeExtension]
$creadListPrec :: ReadPrec [TypeExtension]
readPrec :: ReadPrec TypeExtension
$creadPrec :: ReadPrec TypeExtension
readList :: ReadS [TypeExtension]
$creadList :: ReadS [TypeExtension]
readsPrec :: Int -> ReadS TypeExtension
$creadsPrec :: Int -> ReadS TypeExtension
Read, Int -> TypeExtension -> String -> String
[TypeExtension] -> String -> String
TypeExtension -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeExtension] -> String -> String
$cshowList :: [TypeExtension] -> String -> String
show :: TypeExtension -> String
$cshow :: TypeExtension -> String
showsPrec :: Int -> TypeExtension -> String -> String
$cshowsPrec :: Int -> TypeExtension -> String -> String
Show)

_TypeExtension :: Name
_TypeExtension = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.TypeExtension")

_TypeExtension_scalar :: FieldName
_TypeExtension_scalar = (String -> FieldName
Core.FieldName String
"scalar")

_TypeExtension_object :: FieldName
_TypeExtension_object = (String -> FieldName
Core.FieldName String
"object")

_TypeExtension_interface :: FieldName
_TypeExtension_interface = (String -> FieldName
Core.FieldName String
"interface")

_TypeExtension_union :: FieldName
_TypeExtension_union = (String -> FieldName
Core.FieldName String
"union")

_TypeExtension_enum :: FieldName
_TypeExtension_enum = (String -> FieldName
Core.FieldName String
"enum")

_TypeExtension_inputObject :: FieldName
_TypeExtension_inputObject = (String -> FieldName
Core.FieldName String
"inputObject")

data ScalarTypeDefinition = 
  ScalarTypeDefinition {
    ScalarTypeDefinition -> Maybe Description
scalarTypeDefinitionDescription :: (Maybe Description),
    ScalarTypeDefinition -> Name
scalarTypeDefinitionName :: Name,
    ScalarTypeDefinition -> Maybe Directives
scalarTypeDefinitionDirectives :: (Maybe Directives)}
  deriving (ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
$c/= :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
== :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
$c== :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
Eq, Eq ScalarTypeDefinition
ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
ScalarTypeDefinition -> ScalarTypeDefinition -> Ordering
ScalarTypeDefinition
-> ScalarTypeDefinition -> ScalarTypeDefinition
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
min :: ScalarTypeDefinition
-> ScalarTypeDefinition -> ScalarTypeDefinition
$cmin :: ScalarTypeDefinition
-> ScalarTypeDefinition -> ScalarTypeDefinition
max :: ScalarTypeDefinition
-> ScalarTypeDefinition -> ScalarTypeDefinition
$cmax :: ScalarTypeDefinition
-> ScalarTypeDefinition -> ScalarTypeDefinition
>= :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
$c>= :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
> :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
$c> :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
<= :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
$c<= :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
< :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
$c< :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
compare :: ScalarTypeDefinition -> ScalarTypeDefinition -> Ordering
$ccompare :: ScalarTypeDefinition -> ScalarTypeDefinition -> Ordering
Ord, ReadPrec [ScalarTypeDefinition]
ReadPrec ScalarTypeDefinition
Int -> ReadS ScalarTypeDefinition
ReadS [ScalarTypeDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ScalarTypeDefinition]
$creadListPrec :: ReadPrec [ScalarTypeDefinition]
readPrec :: ReadPrec ScalarTypeDefinition
$creadPrec :: ReadPrec ScalarTypeDefinition
readList :: ReadS [ScalarTypeDefinition]
$creadList :: ReadS [ScalarTypeDefinition]
readsPrec :: Int -> ReadS ScalarTypeDefinition
$creadsPrec :: Int -> ReadS ScalarTypeDefinition
Read, Int -> ScalarTypeDefinition -> String -> String
[ScalarTypeDefinition] -> String -> String
ScalarTypeDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ScalarTypeDefinition] -> String -> String
$cshowList :: [ScalarTypeDefinition] -> String -> String
show :: ScalarTypeDefinition -> String
$cshow :: ScalarTypeDefinition -> String
showsPrec :: Int -> ScalarTypeDefinition -> String -> String
$cshowsPrec :: Int -> ScalarTypeDefinition -> String -> String
Show)

_ScalarTypeDefinition :: Name
_ScalarTypeDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ScalarTypeDefinition")

_ScalarTypeDefinition_description :: FieldName
_ScalarTypeDefinition_description = (String -> FieldName
Core.FieldName String
"description")

_ScalarTypeDefinition_name :: FieldName
_ScalarTypeDefinition_name = (String -> FieldName
Core.FieldName String
"name")

_ScalarTypeDefinition_directives :: FieldName
_ScalarTypeDefinition_directives = (String -> FieldName
Core.FieldName String
"directives")

data ScalarTypeExtension = 
  ScalarTypeExtension {
    ScalarTypeExtension -> Name
scalarTypeExtensionName :: Name,
    ScalarTypeExtension -> Directives
scalarTypeExtensionDirectives :: Directives}
  deriving (ScalarTypeExtension -> ScalarTypeExtension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
$c/= :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
== :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
$c== :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
Eq, Eq ScalarTypeExtension
ScalarTypeExtension -> ScalarTypeExtension -> Bool
ScalarTypeExtension -> ScalarTypeExtension -> Ordering
ScalarTypeExtension -> ScalarTypeExtension -> ScalarTypeExtension
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
min :: ScalarTypeExtension -> ScalarTypeExtension -> ScalarTypeExtension
$cmin :: ScalarTypeExtension -> ScalarTypeExtension -> ScalarTypeExtension
max :: ScalarTypeExtension -> ScalarTypeExtension -> ScalarTypeExtension
$cmax :: ScalarTypeExtension -> ScalarTypeExtension -> ScalarTypeExtension
>= :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
$c>= :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
> :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
$c> :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
<= :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
$c<= :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
< :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
$c< :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
compare :: ScalarTypeExtension -> ScalarTypeExtension -> Ordering
$ccompare :: ScalarTypeExtension -> ScalarTypeExtension -> Ordering
Ord, ReadPrec [ScalarTypeExtension]
ReadPrec ScalarTypeExtension
Int -> ReadS ScalarTypeExtension
ReadS [ScalarTypeExtension]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ScalarTypeExtension]
$creadListPrec :: ReadPrec [ScalarTypeExtension]
readPrec :: ReadPrec ScalarTypeExtension
$creadPrec :: ReadPrec ScalarTypeExtension
readList :: ReadS [ScalarTypeExtension]
$creadList :: ReadS [ScalarTypeExtension]
readsPrec :: Int -> ReadS ScalarTypeExtension
$creadsPrec :: Int -> ReadS ScalarTypeExtension
Read, Int -> ScalarTypeExtension -> String -> String
[ScalarTypeExtension] -> String -> String
ScalarTypeExtension -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ScalarTypeExtension] -> String -> String
$cshowList :: [ScalarTypeExtension] -> String -> String
show :: ScalarTypeExtension -> String
$cshow :: ScalarTypeExtension -> String
showsPrec :: Int -> ScalarTypeExtension -> String -> String
$cshowsPrec :: Int -> ScalarTypeExtension -> String -> String
Show)

_ScalarTypeExtension :: Name
_ScalarTypeExtension = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ScalarTypeExtension")

_ScalarTypeExtension_name :: FieldName
_ScalarTypeExtension_name = (String -> FieldName
Core.FieldName String
"name")

_ScalarTypeExtension_directives :: FieldName
_ScalarTypeExtension_directives = (String -> FieldName
Core.FieldName String
"directives")

data ObjectTypeDefinition = 
  ObjectTypeDefinitionSequence ObjectTypeDefinition_Sequence |
  ObjectTypeDefinitionSequence2 ObjectTypeDefinition_Sequence2
  deriving (ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
$c/= :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
== :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
$c== :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
Eq, Eq ObjectTypeDefinition
ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
ObjectTypeDefinition -> ObjectTypeDefinition -> Ordering
ObjectTypeDefinition
-> ObjectTypeDefinition -> ObjectTypeDefinition
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
min :: ObjectTypeDefinition
-> ObjectTypeDefinition -> ObjectTypeDefinition
$cmin :: ObjectTypeDefinition
-> ObjectTypeDefinition -> ObjectTypeDefinition
max :: ObjectTypeDefinition
-> ObjectTypeDefinition -> ObjectTypeDefinition
$cmax :: ObjectTypeDefinition
-> ObjectTypeDefinition -> ObjectTypeDefinition
>= :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
$c>= :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
> :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
$c> :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
<= :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
$c<= :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
< :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
$c< :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
compare :: ObjectTypeDefinition -> ObjectTypeDefinition -> Ordering
$ccompare :: ObjectTypeDefinition -> ObjectTypeDefinition -> Ordering
Ord, ReadPrec [ObjectTypeDefinition]
ReadPrec ObjectTypeDefinition
Int -> ReadS ObjectTypeDefinition
ReadS [ObjectTypeDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjectTypeDefinition]
$creadListPrec :: ReadPrec [ObjectTypeDefinition]
readPrec :: ReadPrec ObjectTypeDefinition
$creadPrec :: ReadPrec ObjectTypeDefinition
readList :: ReadS [ObjectTypeDefinition]
$creadList :: ReadS [ObjectTypeDefinition]
readsPrec :: Int -> ReadS ObjectTypeDefinition
$creadsPrec :: Int -> ReadS ObjectTypeDefinition
Read, Int -> ObjectTypeDefinition -> String -> String
[ObjectTypeDefinition] -> String -> String
ObjectTypeDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ObjectTypeDefinition] -> String -> String
$cshowList :: [ObjectTypeDefinition] -> String -> String
show :: ObjectTypeDefinition -> String
$cshow :: ObjectTypeDefinition -> String
showsPrec :: Int -> ObjectTypeDefinition -> String -> String
$cshowsPrec :: Int -> ObjectTypeDefinition -> String -> String
Show)

_ObjectTypeDefinition :: Name
_ObjectTypeDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ObjectTypeDefinition")

_ObjectTypeDefinition_sequence :: FieldName
_ObjectTypeDefinition_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_ObjectTypeDefinition_sequence2 :: FieldName
_ObjectTypeDefinition_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data ObjectTypeDefinition_Sequence = 
  ObjectTypeDefinition_Sequence {
    ObjectTypeDefinition_Sequence -> Maybe Description
objectTypeDefinition_SequenceDescription :: (Maybe Description),
    ObjectTypeDefinition_Sequence -> Name
objectTypeDefinition_SequenceName :: Name,
    ObjectTypeDefinition_Sequence -> Maybe ImplementsInterfaces
objectTypeDefinition_SequenceImplementsInterfaces :: (Maybe ImplementsInterfaces),
    ObjectTypeDefinition_Sequence -> Maybe Directives
objectTypeDefinition_SequenceDirectives :: (Maybe Directives),
    ObjectTypeDefinition_Sequence -> FieldsDefinition
objectTypeDefinition_SequenceFieldsDefinition :: FieldsDefinition}
  deriving (ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
$c/= :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
== :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
$c== :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
Eq, Eq ObjectTypeDefinition_Sequence
ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Ordering
ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> ObjectTypeDefinition_Sequence
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
min :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> ObjectTypeDefinition_Sequence
$cmin :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> ObjectTypeDefinition_Sequence
max :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> ObjectTypeDefinition_Sequence
$cmax :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> ObjectTypeDefinition_Sequence
>= :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
$c>= :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
> :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
$c> :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
<= :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
$c<= :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
< :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
$c< :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Bool
compare :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Ordering
$ccompare :: ObjectTypeDefinition_Sequence
-> ObjectTypeDefinition_Sequence -> Ordering
Ord, ReadPrec [ObjectTypeDefinition_Sequence]
ReadPrec ObjectTypeDefinition_Sequence
Int -> ReadS ObjectTypeDefinition_Sequence
ReadS [ObjectTypeDefinition_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjectTypeDefinition_Sequence]
$creadListPrec :: ReadPrec [ObjectTypeDefinition_Sequence]
readPrec :: ReadPrec ObjectTypeDefinition_Sequence
$creadPrec :: ReadPrec ObjectTypeDefinition_Sequence
readList :: ReadS [ObjectTypeDefinition_Sequence]
$creadList :: ReadS [ObjectTypeDefinition_Sequence]
readsPrec :: Int -> ReadS ObjectTypeDefinition_Sequence
$creadsPrec :: Int -> ReadS ObjectTypeDefinition_Sequence
Read, Int -> ObjectTypeDefinition_Sequence -> String -> String
[ObjectTypeDefinition_Sequence] -> String -> String
ObjectTypeDefinition_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ObjectTypeDefinition_Sequence] -> String -> String
$cshowList :: [ObjectTypeDefinition_Sequence] -> String -> String
show :: ObjectTypeDefinition_Sequence -> String
$cshow :: ObjectTypeDefinition_Sequence -> String
showsPrec :: Int -> ObjectTypeDefinition_Sequence -> String -> String
$cshowsPrec :: Int -> ObjectTypeDefinition_Sequence -> String -> String
Show)

_ObjectTypeDefinition_Sequence :: Name
_ObjectTypeDefinition_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ObjectTypeDefinition.Sequence")

_ObjectTypeDefinition_Sequence_description :: FieldName
_ObjectTypeDefinition_Sequence_description = (String -> FieldName
Core.FieldName String
"description")

_ObjectTypeDefinition_Sequence_name :: FieldName
_ObjectTypeDefinition_Sequence_name = (String -> FieldName
Core.FieldName String
"name")

_ObjectTypeDefinition_Sequence_implementsInterfaces :: FieldName
_ObjectTypeDefinition_Sequence_implementsInterfaces = (String -> FieldName
Core.FieldName String
"implementsInterfaces")

_ObjectTypeDefinition_Sequence_directives :: FieldName
_ObjectTypeDefinition_Sequence_directives = (String -> FieldName
Core.FieldName String
"directives")

_ObjectTypeDefinition_Sequence_fieldsDefinition :: FieldName
_ObjectTypeDefinition_Sequence_fieldsDefinition = (String -> FieldName
Core.FieldName String
"fieldsDefinition")

data ObjectTypeDefinition_Sequence2 = 
  ObjectTypeDefinition_Sequence2 {
    ObjectTypeDefinition_Sequence2 -> Maybe Description
objectTypeDefinition_Sequence2Description :: (Maybe Description),
    ObjectTypeDefinition_Sequence2 -> Name
objectTypeDefinition_Sequence2Name :: Name,
    ObjectTypeDefinition_Sequence2 -> Maybe ImplementsInterfaces
objectTypeDefinition_Sequence2ImplementsInterfaces :: (Maybe ImplementsInterfaces),
    ObjectTypeDefinition_Sequence2 -> Maybe Directives
objectTypeDefinition_Sequence2Directives :: (Maybe Directives)}
  deriving (ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
$c/= :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
== :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
$c== :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
Eq, Eq ObjectTypeDefinition_Sequence2
ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Ordering
ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> ObjectTypeDefinition_Sequence2
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
min :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> ObjectTypeDefinition_Sequence2
$cmin :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> ObjectTypeDefinition_Sequence2
max :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> ObjectTypeDefinition_Sequence2
$cmax :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> ObjectTypeDefinition_Sequence2
>= :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
$c>= :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
> :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
$c> :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
<= :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
$c<= :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
< :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
$c< :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Bool
compare :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Ordering
$ccompare :: ObjectTypeDefinition_Sequence2
-> ObjectTypeDefinition_Sequence2 -> Ordering
Ord, ReadPrec [ObjectTypeDefinition_Sequence2]
ReadPrec ObjectTypeDefinition_Sequence2
Int -> ReadS ObjectTypeDefinition_Sequence2
ReadS [ObjectTypeDefinition_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjectTypeDefinition_Sequence2]
$creadListPrec :: ReadPrec [ObjectTypeDefinition_Sequence2]
readPrec :: ReadPrec ObjectTypeDefinition_Sequence2
$creadPrec :: ReadPrec ObjectTypeDefinition_Sequence2
readList :: ReadS [ObjectTypeDefinition_Sequence2]
$creadList :: ReadS [ObjectTypeDefinition_Sequence2]
readsPrec :: Int -> ReadS ObjectTypeDefinition_Sequence2
$creadsPrec :: Int -> ReadS ObjectTypeDefinition_Sequence2
Read, Int -> ObjectTypeDefinition_Sequence2 -> String -> String
[ObjectTypeDefinition_Sequence2] -> String -> String
ObjectTypeDefinition_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ObjectTypeDefinition_Sequence2] -> String -> String
$cshowList :: [ObjectTypeDefinition_Sequence2] -> String -> String
show :: ObjectTypeDefinition_Sequence2 -> String
$cshow :: ObjectTypeDefinition_Sequence2 -> String
showsPrec :: Int -> ObjectTypeDefinition_Sequence2 -> String -> String
$cshowsPrec :: Int -> ObjectTypeDefinition_Sequence2 -> String -> String
Show)

_ObjectTypeDefinition_Sequence2 :: Name
_ObjectTypeDefinition_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ObjectTypeDefinition.Sequence2")

_ObjectTypeDefinition_Sequence2_description :: FieldName
_ObjectTypeDefinition_Sequence2_description = (String -> FieldName
Core.FieldName String
"description")

_ObjectTypeDefinition_Sequence2_name :: FieldName
_ObjectTypeDefinition_Sequence2_name = (String -> FieldName
Core.FieldName String
"name")

_ObjectTypeDefinition_Sequence2_implementsInterfaces :: FieldName
_ObjectTypeDefinition_Sequence2_implementsInterfaces = (String -> FieldName
Core.FieldName String
"implementsInterfaces")

_ObjectTypeDefinition_Sequence2_directives :: FieldName
_ObjectTypeDefinition_Sequence2_directives = (String -> FieldName
Core.FieldName String
"directives")

data ObjectTypeExtension = 
  ObjectTypeExtensionSequence ObjectTypeExtension_Sequence |
  ObjectTypeExtensionSequence2 ObjectTypeExtension_Sequence2 |
  ObjectTypeExtensionSequence3 ObjectTypeExtension_Sequence3
  deriving (ObjectTypeExtension -> ObjectTypeExtension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
$c/= :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
== :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
$c== :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
Eq, Eq ObjectTypeExtension
ObjectTypeExtension -> ObjectTypeExtension -> Bool
ObjectTypeExtension -> ObjectTypeExtension -> Ordering
ObjectTypeExtension -> ObjectTypeExtension -> ObjectTypeExtension
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
min :: ObjectTypeExtension -> ObjectTypeExtension -> ObjectTypeExtension
$cmin :: ObjectTypeExtension -> ObjectTypeExtension -> ObjectTypeExtension
max :: ObjectTypeExtension -> ObjectTypeExtension -> ObjectTypeExtension
$cmax :: ObjectTypeExtension -> ObjectTypeExtension -> ObjectTypeExtension
>= :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
$c>= :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
> :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
$c> :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
<= :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
$c<= :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
< :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
$c< :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
compare :: ObjectTypeExtension -> ObjectTypeExtension -> Ordering
$ccompare :: ObjectTypeExtension -> ObjectTypeExtension -> Ordering
Ord, ReadPrec [ObjectTypeExtension]
ReadPrec ObjectTypeExtension
Int -> ReadS ObjectTypeExtension
ReadS [ObjectTypeExtension]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjectTypeExtension]
$creadListPrec :: ReadPrec [ObjectTypeExtension]
readPrec :: ReadPrec ObjectTypeExtension
$creadPrec :: ReadPrec ObjectTypeExtension
readList :: ReadS [ObjectTypeExtension]
$creadList :: ReadS [ObjectTypeExtension]
readsPrec :: Int -> ReadS ObjectTypeExtension
$creadsPrec :: Int -> ReadS ObjectTypeExtension
Read, Int -> ObjectTypeExtension -> String -> String
[ObjectTypeExtension] -> String -> String
ObjectTypeExtension -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ObjectTypeExtension] -> String -> String
$cshowList :: [ObjectTypeExtension] -> String -> String
show :: ObjectTypeExtension -> String
$cshow :: ObjectTypeExtension -> String
showsPrec :: Int -> ObjectTypeExtension -> String -> String
$cshowsPrec :: Int -> ObjectTypeExtension -> String -> String
Show)

_ObjectTypeExtension :: Name
_ObjectTypeExtension = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ObjectTypeExtension")

_ObjectTypeExtension_sequence :: FieldName
_ObjectTypeExtension_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_ObjectTypeExtension_sequence2 :: FieldName
_ObjectTypeExtension_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

_ObjectTypeExtension_sequence3 :: FieldName
_ObjectTypeExtension_sequence3 = (String -> FieldName
Core.FieldName String
"sequence3")

data ObjectTypeExtension_Sequence = 
  ObjectTypeExtension_Sequence {
    ObjectTypeExtension_Sequence -> Name
objectTypeExtension_SequenceName :: Name,
    ObjectTypeExtension_Sequence -> Maybe ImplementsInterfaces
objectTypeExtension_SequenceImplementsInterfaces :: (Maybe ImplementsInterfaces),
    ObjectTypeExtension_Sequence -> Maybe Directives
objectTypeExtension_SequenceDirectives :: (Maybe Directives),
    ObjectTypeExtension_Sequence -> FieldsDefinition
objectTypeExtension_SequenceFieldsDefinition :: FieldsDefinition}
  deriving (ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
$c/= :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
== :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
$c== :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
Eq, Eq ObjectTypeExtension_Sequence
ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Ordering
ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> ObjectTypeExtension_Sequence
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
min :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> ObjectTypeExtension_Sequence
$cmin :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> ObjectTypeExtension_Sequence
max :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> ObjectTypeExtension_Sequence
$cmax :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> ObjectTypeExtension_Sequence
>= :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
$c>= :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
> :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
$c> :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
<= :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
$c<= :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
< :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
$c< :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
compare :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Ordering
$ccompare :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Ordering
Ord, ReadPrec [ObjectTypeExtension_Sequence]
ReadPrec ObjectTypeExtension_Sequence
Int -> ReadS ObjectTypeExtension_Sequence
ReadS [ObjectTypeExtension_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjectTypeExtension_Sequence]
$creadListPrec :: ReadPrec [ObjectTypeExtension_Sequence]
readPrec :: ReadPrec ObjectTypeExtension_Sequence
$creadPrec :: ReadPrec ObjectTypeExtension_Sequence
readList :: ReadS [ObjectTypeExtension_Sequence]
$creadList :: ReadS [ObjectTypeExtension_Sequence]
readsPrec :: Int -> ReadS ObjectTypeExtension_Sequence
$creadsPrec :: Int -> ReadS ObjectTypeExtension_Sequence
Read, Int -> ObjectTypeExtension_Sequence -> String -> String
[ObjectTypeExtension_Sequence] -> String -> String
ObjectTypeExtension_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ObjectTypeExtension_Sequence] -> String -> String
$cshowList :: [ObjectTypeExtension_Sequence] -> String -> String
show :: ObjectTypeExtension_Sequence -> String
$cshow :: ObjectTypeExtension_Sequence -> String
showsPrec :: Int -> ObjectTypeExtension_Sequence -> String -> String
$cshowsPrec :: Int -> ObjectTypeExtension_Sequence -> String -> String
Show)

_ObjectTypeExtension_Sequence :: Name
_ObjectTypeExtension_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ObjectTypeExtension.Sequence")

_ObjectTypeExtension_Sequence_name :: FieldName
_ObjectTypeExtension_Sequence_name = (String -> FieldName
Core.FieldName String
"name")

_ObjectTypeExtension_Sequence_implementsInterfaces :: FieldName
_ObjectTypeExtension_Sequence_implementsInterfaces = (String -> FieldName
Core.FieldName String
"implementsInterfaces")

_ObjectTypeExtension_Sequence_directives :: FieldName
_ObjectTypeExtension_Sequence_directives = (String -> FieldName
Core.FieldName String
"directives")

_ObjectTypeExtension_Sequence_fieldsDefinition :: FieldName
_ObjectTypeExtension_Sequence_fieldsDefinition = (String -> FieldName
Core.FieldName String
"fieldsDefinition")

data ObjectTypeExtension_Sequence2 = 
  ObjectTypeExtension_Sequence2 {
    ObjectTypeExtension_Sequence2 -> Name
objectTypeExtension_Sequence2Name :: Name,
    ObjectTypeExtension_Sequence2 -> Maybe ImplementsInterfaces
objectTypeExtension_Sequence2ImplementsInterfaces :: (Maybe ImplementsInterfaces),
    ObjectTypeExtension_Sequence2 -> Maybe Directives
objectTypeExtension_Sequence2Directives :: (Maybe Directives)}
  deriving (ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
$c/= :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
== :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
$c== :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
Eq, Eq ObjectTypeExtension_Sequence2
ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Ordering
ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> ObjectTypeExtension_Sequence2
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
min :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> ObjectTypeExtension_Sequence2
$cmin :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> ObjectTypeExtension_Sequence2
max :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> ObjectTypeExtension_Sequence2
$cmax :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> ObjectTypeExtension_Sequence2
>= :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
$c>= :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
> :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
$c> :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
<= :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
$c<= :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
< :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
$c< :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
compare :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Ordering
$ccompare :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Ordering
Ord, ReadPrec [ObjectTypeExtension_Sequence2]
ReadPrec ObjectTypeExtension_Sequence2
Int -> ReadS ObjectTypeExtension_Sequence2
ReadS [ObjectTypeExtension_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjectTypeExtension_Sequence2]
$creadListPrec :: ReadPrec [ObjectTypeExtension_Sequence2]
readPrec :: ReadPrec ObjectTypeExtension_Sequence2
$creadPrec :: ReadPrec ObjectTypeExtension_Sequence2
readList :: ReadS [ObjectTypeExtension_Sequence2]
$creadList :: ReadS [ObjectTypeExtension_Sequence2]
readsPrec :: Int -> ReadS ObjectTypeExtension_Sequence2
$creadsPrec :: Int -> ReadS ObjectTypeExtension_Sequence2
Read, Int -> ObjectTypeExtension_Sequence2 -> String -> String
[ObjectTypeExtension_Sequence2] -> String -> String
ObjectTypeExtension_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ObjectTypeExtension_Sequence2] -> String -> String
$cshowList :: [ObjectTypeExtension_Sequence2] -> String -> String
show :: ObjectTypeExtension_Sequence2 -> String
$cshow :: ObjectTypeExtension_Sequence2 -> String
showsPrec :: Int -> ObjectTypeExtension_Sequence2 -> String -> String
$cshowsPrec :: Int -> ObjectTypeExtension_Sequence2 -> String -> String
Show)

_ObjectTypeExtension_Sequence2 :: Name
_ObjectTypeExtension_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ObjectTypeExtension.Sequence2")

_ObjectTypeExtension_Sequence2_name :: FieldName
_ObjectTypeExtension_Sequence2_name = (String -> FieldName
Core.FieldName String
"name")

_ObjectTypeExtension_Sequence2_implementsInterfaces :: FieldName
_ObjectTypeExtension_Sequence2_implementsInterfaces = (String -> FieldName
Core.FieldName String
"implementsInterfaces")

_ObjectTypeExtension_Sequence2_directives :: FieldName
_ObjectTypeExtension_Sequence2_directives = (String -> FieldName
Core.FieldName String
"directives")

data ObjectTypeExtension_Sequence3 = 
  ObjectTypeExtension_Sequence3 {
    ObjectTypeExtension_Sequence3 -> Name
objectTypeExtension_Sequence3Name :: Name,
    ObjectTypeExtension_Sequence3 -> ImplementsInterfaces
objectTypeExtension_Sequence3ImplementsInterfaces :: ImplementsInterfaces}
  deriving (ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
$c/= :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
== :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
$c== :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
Eq, Eq ObjectTypeExtension_Sequence3
ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Ordering
ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> ObjectTypeExtension_Sequence3
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
min :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> ObjectTypeExtension_Sequence3
$cmin :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> ObjectTypeExtension_Sequence3
max :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> ObjectTypeExtension_Sequence3
$cmax :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> ObjectTypeExtension_Sequence3
>= :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
$c>= :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
> :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
$c> :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
<= :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
$c<= :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
< :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
$c< :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
compare :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Ordering
$ccompare :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Ordering
Ord, ReadPrec [ObjectTypeExtension_Sequence3]
ReadPrec ObjectTypeExtension_Sequence3
Int -> ReadS ObjectTypeExtension_Sequence3
ReadS [ObjectTypeExtension_Sequence3]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ObjectTypeExtension_Sequence3]
$creadListPrec :: ReadPrec [ObjectTypeExtension_Sequence3]
readPrec :: ReadPrec ObjectTypeExtension_Sequence3
$creadPrec :: ReadPrec ObjectTypeExtension_Sequence3
readList :: ReadS [ObjectTypeExtension_Sequence3]
$creadList :: ReadS [ObjectTypeExtension_Sequence3]
readsPrec :: Int -> ReadS ObjectTypeExtension_Sequence3
$creadsPrec :: Int -> ReadS ObjectTypeExtension_Sequence3
Read, Int -> ObjectTypeExtension_Sequence3 -> String -> String
[ObjectTypeExtension_Sequence3] -> String -> String
ObjectTypeExtension_Sequence3 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ObjectTypeExtension_Sequence3] -> String -> String
$cshowList :: [ObjectTypeExtension_Sequence3] -> String -> String
show :: ObjectTypeExtension_Sequence3 -> String
$cshow :: ObjectTypeExtension_Sequence3 -> String
showsPrec :: Int -> ObjectTypeExtension_Sequence3 -> String -> String
$cshowsPrec :: Int -> ObjectTypeExtension_Sequence3 -> String -> String
Show)

_ObjectTypeExtension_Sequence3 :: Name
_ObjectTypeExtension_Sequence3 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ObjectTypeExtension.Sequence3")

_ObjectTypeExtension_Sequence3_name :: FieldName
_ObjectTypeExtension_Sequence3_name = (String -> FieldName
Core.FieldName String
"name")

_ObjectTypeExtension_Sequence3_implementsInterfaces :: FieldName
_ObjectTypeExtension_Sequence3_implementsInterfaces = (String -> FieldName
Core.FieldName String
"implementsInterfaces")

data ImplementsInterfaces = 
  ImplementsInterfacesSequence ImplementsInterfaces_Sequence |
  ImplementsInterfacesSequence2 ImplementsInterfaces_Sequence2
  deriving (ImplementsInterfaces -> ImplementsInterfaces -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
$c/= :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
== :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
$c== :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
Eq, Eq ImplementsInterfaces
ImplementsInterfaces -> ImplementsInterfaces -> Bool
ImplementsInterfaces -> ImplementsInterfaces -> Ordering
ImplementsInterfaces
-> ImplementsInterfaces -> ImplementsInterfaces
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
min :: ImplementsInterfaces
-> ImplementsInterfaces -> ImplementsInterfaces
$cmin :: ImplementsInterfaces
-> ImplementsInterfaces -> ImplementsInterfaces
max :: ImplementsInterfaces
-> ImplementsInterfaces -> ImplementsInterfaces
$cmax :: ImplementsInterfaces
-> ImplementsInterfaces -> ImplementsInterfaces
>= :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
$c>= :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
> :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
$c> :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
<= :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
$c<= :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
< :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
$c< :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
compare :: ImplementsInterfaces -> ImplementsInterfaces -> Ordering
$ccompare :: ImplementsInterfaces -> ImplementsInterfaces -> Ordering
Ord, ReadPrec [ImplementsInterfaces]
ReadPrec ImplementsInterfaces
Int -> ReadS ImplementsInterfaces
ReadS [ImplementsInterfaces]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImplementsInterfaces]
$creadListPrec :: ReadPrec [ImplementsInterfaces]
readPrec :: ReadPrec ImplementsInterfaces
$creadPrec :: ReadPrec ImplementsInterfaces
readList :: ReadS [ImplementsInterfaces]
$creadList :: ReadS [ImplementsInterfaces]
readsPrec :: Int -> ReadS ImplementsInterfaces
$creadsPrec :: Int -> ReadS ImplementsInterfaces
Read, Int -> ImplementsInterfaces -> String -> String
[ImplementsInterfaces] -> String -> String
ImplementsInterfaces -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ImplementsInterfaces] -> String -> String
$cshowList :: [ImplementsInterfaces] -> String -> String
show :: ImplementsInterfaces -> String
$cshow :: ImplementsInterfaces -> String
showsPrec :: Int -> ImplementsInterfaces -> String -> String
$cshowsPrec :: Int -> ImplementsInterfaces -> String -> String
Show)

_ImplementsInterfaces :: Name
_ImplementsInterfaces = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ImplementsInterfaces")

_ImplementsInterfaces_sequence :: FieldName
_ImplementsInterfaces_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_ImplementsInterfaces_sequence2 :: FieldName
_ImplementsInterfaces_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data ImplementsInterfaces_Sequence = 
  ImplementsInterfaces_Sequence {
    ImplementsInterfaces_Sequence -> ImplementsInterfaces
implementsInterfaces_SequenceImplementsInterfaces :: ImplementsInterfaces,
    ImplementsInterfaces_Sequence -> NamedType
implementsInterfaces_SequenceNamedType :: NamedType}
  deriving (ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
$c/= :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
== :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
$c== :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
Eq, Eq ImplementsInterfaces_Sequence
ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Ordering
ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> ImplementsInterfaces_Sequence
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
min :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> ImplementsInterfaces_Sequence
$cmin :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> ImplementsInterfaces_Sequence
max :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> ImplementsInterfaces_Sequence
$cmax :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> ImplementsInterfaces_Sequence
>= :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
$c>= :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
> :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
$c> :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
<= :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
$c<= :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
< :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
$c< :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
compare :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Ordering
$ccompare :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Ordering
Ord, ReadPrec [ImplementsInterfaces_Sequence]
ReadPrec ImplementsInterfaces_Sequence
Int -> ReadS ImplementsInterfaces_Sequence
ReadS [ImplementsInterfaces_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImplementsInterfaces_Sequence]
$creadListPrec :: ReadPrec [ImplementsInterfaces_Sequence]
readPrec :: ReadPrec ImplementsInterfaces_Sequence
$creadPrec :: ReadPrec ImplementsInterfaces_Sequence
readList :: ReadS [ImplementsInterfaces_Sequence]
$creadList :: ReadS [ImplementsInterfaces_Sequence]
readsPrec :: Int -> ReadS ImplementsInterfaces_Sequence
$creadsPrec :: Int -> ReadS ImplementsInterfaces_Sequence
Read, Int -> ImplementsInterfaces_Sequence -> String -> String
[ImplementsInterfaces_Sequence] -> String -> String
ImplementsInterfaces_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ImplementsInterfaces_Sequence] -> String -> String
$cshowList :: [ImplementsInterfaces_Sequence] -> String -> String
show :: ImplementsInterfaces_Sequence -> String
$cshow :: ImplementsInterfaces_Sequence -> String
showsPrec :: Int -> ImplementsInterfaces_Sequence -> String -> String
$cshowsPrec :: Int -> ImplementsInterfaces_Sequence -> String -> String
Show)

_ImplementsInterfaces_Sequence :: Name
_ImplementsInterfaces_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ImplementsInterfaces.Sequence")

_ImplementsInterfaces_Sequence_implementsInterfaces :: FieldName
_ImplementsInterfaces_Sequence_implementsInterfaces = (String -> FieldName
Core.FieldName String
"implementsInterfaces")

_ImplementsInterfaces_Sequence_namedType :: FieldName
_ImplementsInterfaces_Sequence_namedType = (String -> FieldName
Core.FieldName String
"namedType")

data ImplementsInterfaces_Sequence2 = 
  ImplementsInterfaces_Sequence2 {
    ImplementsInterfaces_Sequence2 -> Maybe ()
implementsInterfaces_Sequence2Amp :: (Maybe ()),
    ImplementsInterfaces_Sequence2 -> NamedType
implementsInterfaces_Sequence2NamedType :: NamedType}
  deriving (ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
$c/= :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
== :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
$c== :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
Eq, Eq ImplementsInterfaces_Sequence2
ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Ordering
ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> ImplementsInterfaces_Sequence2
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
min :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> ImplementsInterfaces_Sequence2
$cmin :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> ImplementsInterfaces_Sequence2
max :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> ImplementsInterfaces_Sequence2
$cmax :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> ImplementsInterfaces_Sequence2
>= :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
$c>= :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
> :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
$c> :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
<= :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
$c<= :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
< :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
$c< :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
compare :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Ordering
$ccompare :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Ordering
Ord, ReadPrec [ImplementsInterfaces_Sequence2]
ReadPrec ImplementsInterfaces_Sequence2
Int -> ReadS ImplementsInterfaces_Sequence2
ReadS [ImplementsInterfaces_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ImplementsInterfaces_Sequence2]
$creadListPrec :: ReadPrec [ImplementsInterfaces_Sequence2]
readPrec :: ReadPrec ImplementsInterfaces_Sequence2
$creadPrec :: ReadPrec ImplementsInterfaces_Sequence2
readList :: ReadS [ImplementsInterfaces_Sequence2]
$creadList :: ReadS [ImplementsInterfaces_Sequence2]
readsPrec :: Int -> ReadS ImplementsInterfaces_Sequence2
$creadsPrec :: Int -> ReadS ImplementsInterfaces_Sequence2
Read, Int -> ImplementsInterfaces_Sequence2 -> String -> String
[ImplementsInterfaces_Sequence2] -> String -> String
ImplementsInterfaces_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ImplementsInterfaces_Sequence2] -> String -> String
$cshowList :: [ImplementsInterfaces_Sequence2] -> String -> String
show :: ImplementsInterfaces_Sequence2 -> String
$cshow :: ImplementsInterfaces_Sequence2 -> String
showsPrec :: Int -> ImplementsInterfaces_Sequence2 -> String -> String
$cshowsPrec :: Int -> ImplementsInterfaces_Sequence2 -> String -> String
Show)

_ImplementsInterfaces_Sequence2 :: Name
_ImplementsInterfaces_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ImplementsInterfaces.Sequence2")

_ImplementsInterfaces_Sequence2_amp :: FieldName
_ImplementsInterfaces_Sequence2_amp = (String -> FieldName
Core.FieldName String
"amp")

_ImplementsInterfaces_Sequence2_namedType :: FieldName
_ImplementsInterfaces_Sequence2_namedType = (String -> FieldName
Core.FieldName String
"namedType")

data FieldsDefinition = 
  FieldsDefinition {
    FieldsDefinition -> [FieldDefinition]
fieldsDefinitionListOfFieldDefinition :: [FieldDefinition]}
  deriving (FieldsDefinition -> FieldsDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldsDefinition -> FieldsDefinition -> Bool
$c/= :: FieldsDefinition -> FieldsDefinition -> Bool
== :: FieldsDefinition -> FieldsDefinition -> Bool
$c== :: FieldsDefinition -> FieldsDefinition -> Bool
Eq, Eq FieldsDefinition
FieldsDefinition -> FieldsDefinition -> Bool
FieldsDefinition -> FieldsDefinition -> Ordering
FieldsDefinition -> FieldsDefinition -> FieldsDefinition
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
min :: FieldsDefinition -> FieldsDefinition -> FieldsDefinition
$cmin :: FieldsDefinition -> FieldsDefinition -> FieldsDefinition
max :: FieldsDefinition -> FieldsDefinition -> FieldsDefinition
$cmax :: FieldsDefinition -> FieldsDefinition -> FieldsDefinition
>= :: FieldsDefinition -> FieldsDefinition -> Bool
$c>= :: FieldsDefinition -> FieldsDefinition -> Bool
> :: FieldsDefinition -> FieldsDefinition -> Bool
$c> :: FieldsDefinition -> FieldsDefinition -> Bool
<= :: FieldsDefinition -> FieldsDefinition -> Bool
$c<= :: FieldsDefinition -> FieldsDefinition -> Bool
< :: FieldsDefinition -> FieldsDefinition -> Bool
$c< :: FieldsDefinition -> FieldsDefinition -> Bool
compare :: FieldsDefinition -> FieldsDefinition -> Ordering
$ccompare :: FieldsDefinition -> FieldsDefinition -> Ordering
Ord, ReadPrec [FieldsDefinition]
ReadPrec FieldsDefinition
Int -> ReadS FieldsDefinition
ReadS [FieldsDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldsDefinition]
$creadListPrec :: ReadPrec [FieldsDefinition]
readPrec :: ReadPrec FieldsDefinition
$creadPrec :: ReadPrec FieldsDefinition
readList :: ReadS [FieldsDefinition]
$creadList :: ReadS [FieldsDefinition]
readsPrec :: Int -> ReadS FieldsDefinition
$creadsPrec :: Int -> ReadS FieldsDefinition
Read, Int -> FieldsDefinition -> String -> String
[FieldsDefinition] -> String -> String
FieldsDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FieldsDefinition] -> String -> String
$cshowList :: [FieldsDefinition] -> String -> String
show :: FieldsDefinition -> String
$cshow :: FieldsDefinition -> String
showsPrec :: Int -> FieldsDefinition -> String -> String
$cshowsPrec :: Int -> FieldsDefinition -> String -> String
Show)

_FieldsDefinition :: Name
_FieldsDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.FieldsDefinition")

_FieldsDefinition_listOfFieldDefinition :: FieldName
_FieldsDefinition_listOfFieldDefinition = (String -> FieldName
Core.FieldName String
"listOfFieldDefinition")

data FieldDefinition = 
  FieldDefinition {
    FieldDefinition -> Maybe Description
fieldDefinitionDescription :: (Maybe Description),
    FieldDefinition -> Name
fieldDefinitionName :: Name,
    FieldDefinition -> Maybe ArgumentsDefinition
fieldDefinitionArgumentsDefinition :: (Maybe ArgumentsDefinition),
    FieldDefinition -> Type
fieldDefinitionType :: Type,
    FieldDefinition -> Maybe Directives
fieldDefinitionDirectives :: (Maybe Directives)}
  deriving (FieldDefinition -> FieldDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FieldDefinition -> FieldDefinition -> Bool
$c/= :: FieldDefinition -> FieldDefinition -> Bool
== :: FieldDefinition -> FieldDefinition -> Bool
$c== :: FieldDefinition -> FieldDefinition -> Bool
Eq, Eq FieldDefinition
FieldDefinition -> FieldDefinition -> Bool
FieldDefinition -> FieldDefinition -> Ordering
FieldDefinition -> FieldDefinition -> FieldDefinition
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
min :: FieldDefinition -> FieldDefinition -> FieldDefinition
$cmin :: FieldDefinition -> FieldDefinition -> FieldDefinition
max :: FieldDefinition -> FieldDefinition -> FieldDefinition
$cmax :: FieldDefinition -> FieldDefinition -> FieldDefinition
>= :: FieldDefinition -> FieldDefinition -> Bool
$c>= :: FieldDefinition -> FieldDefinition -> Bool
> :: FieldDefinition -> FieldDefinition -> Bool
$c> :: FieldDefinition -> FieldDefinition -> Bool
<= :: FieldDefinition -> FieldDefinition -> Bool
$c<= :: FieldDefinition -> FieldDefinition -> Bool
< :: FieldDefinition -> FieldDefinition -> Bool
$c< :: FieldDefinition -> FieldDefinition -> Bool
compare :: FieldDefinition -> FieldDefinition -> Ordering
$ccompare :: FieldDefinition -> FieldDefinition -> Ordering
Ord, ReadPrec [FieldDefinition]
ReadPrec FieldDefinition
Int -> ReadS FieldDefinition
ReadS [FieldDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [FieldDefinition]
$creadListPrec :: ReadPrec [FieldDefinition]
readPrec :: ReadPrec FieldDefinition
$creadPrec :: ReadPrec FieldDefinition
readList :: ReadS [FieldDefinition]
$creadList :: ReadS [FieldDefinition]
readsPrec :: Int -> ReadS FieldDefinition
$creadsPrec :: Int -> ReadS FieldDefinition
Read, Int -> FieldDefinition -> String -> String
[FieldDefinition] -> String -> String
FieldDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [FieldDefinition] -> String -> String
$cshowList :: [FieldDefinition] -> String -> String
show :: FieldDefinition -> String
$cshow :: FieldDefinition -> String
showsPrec :: Int -> FieldDefinition -> String -> String
$cshowsPrec :: Int -> FieldDefinition -> String -> String
Show)

_FieldDefinition :: Name
_FieldDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.FieldDefinition")

_FieldDefinition_description :: FieldName
_FieldDefinition_description = (String -> FieldName
Core.FieldName String
"description")

_FieldDefinition_name :: FieldName
_FieldDefinition_name = (String -> FieldName
Core.FieldName String
"name")

_FieldDefinition_argumentsDefinition :: FieldName
_FieldDefinition_argumentsDefinition = (String -> FieldName
Core.FieldName String
"argumentsDefinition")

_FieldDefinition_type :: FieldName
_FieldDefinition_type = (String -> FieldName
Core.FieldName String
"type")

_FieldDefinition_directives :: FieldName
_FieldDefinition_directives = (String -> FieldName
Core.FieldName String
"directives")

data ArgumentsDefinition = 
  ArgumentsDefinition {
    ArgumentsDefinition -> [InputValueDefinition]
argumentsDefinitionListOfInputValueDefinition :: [InputValueDefinition]}
  deriving (ArgumentsDefinition -> ArgumentsDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
$c/= :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
== :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
$c== :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
Eq, Eq ArgumentsDefinition
ArgumentsDefinition -> ArgumentsDefinition -> Bool
ArgumentsDefinition -> ArgumentsDefinition -> Ordering
ArgumentsDefinition -> ArgumentsDefinition -> ArgumentsDefinition
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
min :: ArgumentsDefinition -> ArgumentsDefinition -> ArgumentsDefinition
$cmin :: ArgumentsDefinition -> ArgumentsDefinition -> ArgumentsDefinition
max :: ArgumentsDefinition -> ArgumentsDefinition -> ArgumentsDefinition
$cmax :: ArgumentsDefinition -> ArgumentsDefinition -> ArgumentsDefinition
>= :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
$c>= :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
> :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
$c> :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
<= :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
$c<= :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
< :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
$c< :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
compare :: ArgumentsDefinition -> ArgumentsDefinition -> Ordering
$ccompare :: ArgumentsDefinition -> ArgumentsDefinition -> Ordering
Ord, ReadPrec [ArgumentsDefinition]
ReadPrec ArgumentsDefinition
Int -> ReadS ArgumentsDefinition
ReadS [ArgumentsDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ArgumentsDefinition]
$creadListPrec :: ReadPrec [ArgumentsDefinition]
readPrec :: ReadPrec ArgumentsDefinition
$creadPrec :: ReadPrec ArgumentsDefinition
readList :: ReadS [ArgumentsDefinition]
$creadList :: ReadS [ArgumentsDefinition]
readsPrec :: Int -> ReadS ArgumentsDefinition
$creadsPrec :: Int -> ReadS ArgumentsDefinition
Read, Int -> ArgumentsDefinition -> String -> String
[ArgumentsDefinition] -> String -> String
ArgumentsDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ArgumentsDefinition] -> String -> String
$cshowList :: [ArgumentsDefinition] -> String -> String
show :: ArgumentsDefinition -> String
$cshow :: ArgumentsDefinition -> String
showsPrec :: Int -> ArgumentsDefinition -> String -> String
$cshowsPrec :: Int -> ArgumentsDefinition -> String -> String
Show)

_ArgumentsDefinition :: Name
_ArgumentsDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ArgumentsDefinition")

_ArgumentsDefinition_listOfInputValueDefinition :: FieldName
_ArgumentsDefinition_listOfInputValueDefinition = (String -> FieldName
Core.FieldName String
"listOfInputValueDefinition")

data InputValueDefinition = 
  InputValueDefinition {
    InputValueDefinition -> Maybe Description
inputValueDefinitionDescription :: (Maybe Description),
    InputValueDefinition -> Name
inputValueDefinitionName :: Name,
    InputValueDefinition -> Type
inputValueDefinitionType :: Type,
    InputValueDefinition -> Maybe DefaultValue
inputValueDefinitionDefaultValue :: (Maybe DefaultValue),
    InputValueDefinition -> Maybe Directives
inputValueDefinitionDirectives :: (Maybe Directives)}
  deriving (InputValueDefinition -> InputValueDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputValueDefinition -> InputValueDefinition -> Bool
$c/= :: InputValueDefinition -> InputValueDefinition -> Bool
== :: InputValueDefinition -> InputValueDefinition -> Bool
$c== :: InputValueDefinition -> InputValueDefinition -> Bool
Eq, Eq InputValueDefinition
InputValueDefinition -> InputValueDefinition -> Bool
InputValueDefinition -> InputValueDefinition -> Ordering
InputValueDefinition
-> InputValueDefinition -> InputValueDefinition
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
min :: InputValueDefinition
-> InputValueDefinition -> InputValueDefinition
$cmin :: InputValueDefinition
-> InputValueDefinition -> InputValueDefinition
max :: InputValueDefinition
-> InputValueDefinition -> InputValueDefinition
$cmax :: InputValueDefinition
-> InputValueDefinition -> InputValueDefinition
>= :: InputValueDefinition -> InputValueDefinition -> Bool
$c>= :: InputValueDefinition -> InputValueDefinition -> Bool
> :: InputValueDefinition -> InputValueDefinition -> Bool
$c> :: InputValueDefinition -> InputValueDefinition -> Bool
<= :: InputValueDefinition -> InputValueDefinition -> Bool
$c<= :: InputValueDefinition -> InputValueDefinition -> Bool
< :: InputValueDefinition -> InputValueDefinition -> Bool
$c< :: InputValueDefinition -> InputValueDefinition -> Bool
compare :: InputValueDefinition -> InputValueDefinition -> Ordering
$ccompare :: InputValueDefinition -> InputValueDefinition -> Ordering
Ord, ReadPrec [InputValueDefinition]
ReadPrec InputValueDefinition
Int -> ReadS InputValueDefinition
ReadS [InputValueDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InputValueDefinition]
$creadListPrec :: ReadPrec [InputValueDefinition]
readPrec :: ReadPrec InputValueDefinition
$creadPrec :: ReadPrec InputValueDefinition
readList :: ReadS [InputValueDefinition]
$creadList :: ReadS [InputValueDefinition]
readsPrec :: Int -> ReadS InputValueDefinition
$creadsPrec :: Int -> ReadS InputValueDefinition
Read, Int -> InputValueDefinition -> String -> String
[InputValueDefinition] -> String -> String
InputValueDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InputValueDefinition] -> String -> String
$cshowList :: [InputValueDefinition] -> String -> String
show :: InputValueDefinition -> String
$cshow :: InputValueDefinition -> String
showsPrec :: Int -> InputValueDefinition -> String -> String
$cshowsPrec :: Int -> InputValueDefinition -> String -> String
Show)

_InputValueDefinition :: Name
_InputValueDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InputValueDefinition")

_InputValueDefinition_description :: FieldName
_InputValueDefinition_description = (String -> FieldName
Core.FieldName String
"description")

_InputValueDefinition_name :: FieldName
_InputValueDefinition_name = (String -> FieldName
Core.FieldName String
"name")

_InputValueDefinition_type :: FieldName
_InputValueDefinition_type = (String -> FieldName
Core.FieldName String
"type")

_InputValueDefinition_defaultValue :: FieldName
_InputValueDefinition_defaultValue = (String -> FieldName
Core.FieldName String
"defaultValue")

_InputValueDefinition_directives :: FieldName
_InputValueDefinition_directives = (String -> FieldName
Core.FieldName String
"directives")

data InterfaceTypeDefinition = 
  InterfaceTypeDefinitionSequence InterfaceTypeDefinition_Sequence |
  InterfaceTypeDefinitionSequence2 InterfaceTypeDefinition_Sequence2
  deriving (InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
$c/= :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
== :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
$c== :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
Eq, Eq InterfaceTypeDefinition
InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
InterfaceTypeDefinition -> InterfaceTypeDefinition -> Ordering
InterfaceTypeDefinition
-> InterfaceTypeDefinition -> InterfaceTypeDefinition
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
min :: InterfaceTypeDefinition
-> InterfaceTypeDefinition -> InterfaceTypeDefinition
$cmin :: InterfaceTypeDefinition
-> InterfaceTypeDefinition -> InterfaceTypeDefinition
max :: InterfaceTypeDefinition
-> InterfaceTypeDefinition -> InterfaceTypeDefinition
$cmax :: InterfaceTypeDefinition
-> InterfaceTypeDefinition -> InterfaceTypeDefinition
>= :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
$c>= :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
> :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
$c> :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
<= :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
$c<= :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
< :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
$c< :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
compare :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Ordering
$ccompare :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Ordering
Ord, ReadPrec [InterfaceTypeDefinition]
ReadPrec InterfaceTypeDefinition
Int -> ReadS InterfaceTypeDefinition
ReadS [InterfaceTypeDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceTypeDefinition]
$creadListPrec :: ReadPrec [InterfaceTypeDefinition]
readPrec :: ReadPrec InterfaceTypeDefinition
$creadPrec :: ReadPrec InterfaceTypeDefinition
readList :: ReadS [InterfaceTypeDefinition]
$creadList :: ReadS [InterfaceTypeDefinition]
readsPrec :: Int -> ReadS InterfaceTypeDefinition
$creadsPrec :: Int -> ReadS InterfaceTypeDefinition
Read, Int -> InterfaceTypeDefinition -> String -> String
[InterfaceTypeDefinition] -> String -> String
InterfaceTypeDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceTypeDefinition] -> String -> String
$cshowList :: [InterfaceTypeDefinition] -> String -> String
show :: InterfaceTypeDefinition -> String
$cshow :: InterfaceTypeDefinition -> String
showsPrec :: Int -> InterfaceTypeDefinition -> String -> String
$cshowsPrec :: Int -> InterfaceTypeDefinition -> String -> String
Show)

_InterfaceTypeDefinition :: Name
_InterfaceTypeDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InterfaceTypeDefinition")

_InterfaceTypeDefinition_sequence :: FieldName
_InterfaceTypeDefinition_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_InterfaceTypeDefinition_sequence2 :: FieldName
_InterfaceTypeDefinition_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data InterfaceTypeDefinition_Sequence = 
  InterfaceTypeDefinition_Sequence {
    InterfaceTypeDefinition_Sequence -> Maybe Description
interfaceTypeDefinition_SequenceDescription :: (Maybe Description),
    InterfaceTypeDefinition_Sequence -> Name
interfaceTypeDefinition_SequenceName :: Name,
    InterfaceTypeDefinition_Sequence -> Maybe ImplementsInterfaces
interfaceTypeDefinition_SequenceImplementsInterfaces :: (Maybe ImplementsInterfaces),
    InterfaceTypeDefinition_Sequence -> Maybe Directives
interfaceTypeDefinition_SequenceDirectives :: (Maybe Directives),
    InterfaceTypeDefinition_Sequence -> FieldsDefinition
interfaceTypeDefinition_SequenceFieldsDefinition :: FieldsDefinition}
  deriving (InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
$c/= :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
== :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
$c== :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
Eq, Eq InterfaceTypeDefinition_Sequence
InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Ordering
InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
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
min :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
$cmin :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
max :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
$cmax :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
>= :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
$c>= :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
> :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
$c> :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
<= :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
$c<= :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
< :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
$c< :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
compare :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Ordering
$ccompare :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Ordering
Ord, ReadPrec [InterfaceTypeDefinition_Sequence]
ReadPrec InterfaceTypeDefinition_Sequence
Int -> ReadS InterfaceTypeDefinition_Sequence
ReadS [InterfaceTypeDefinition_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceTypeDefinition_Sequence]
$creadListPrec :: ReadPrec [InterfaceTypeDefinition_Sequence]
readPrec :: ReadPrec InterfaceTypeDefinition_Sequence
$creadPrec :: ReadPrec InterfaceTypeDefinition_Sequence
readList :: ReadS [InterfaceTypeDefinition_Sequence]
$creadList :: ReadS [InterfaceTypeDefinition_Sequence]
readsPrec :: Int -> ReadS InterfaceTypeDefinition_Sequence
$creadsPrec :: Int -> ReadS InterfaceTypeDefinition_Sequence
Read, Int -> InterfaceTypeDefinition_Sequence -> String -> String
[InterfaceTypeDefinition_Sequence] -> String -> String
InterfaceTypeDefinition_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceTypeDefinition_Sequence] -> String -> String
$cshowList :: [InterfaceTypeDefinition_Sequence] -> String -> String
show :: InterfaceTypeDefinition_Sequence -> String
$cshow :: InterfaceTypeDefinition_Sequence -> String
showsPrec :: Int -> InterfaceTypeDefinition_Sequence -> String -> String
$cshowsPrec :: Int -> InterfaceTypeDefinition_Sequence -> String -> String
Show)

_InterfaceTypeDefinition_Sequence :: Name
_InterfaceTypeDefinition_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InterfaceTypeDefinition.Sequence")

_InterfaceTypeDefinition_Sequence_description :: FieldName
_InterfaceTypeDefinition_Sequence_description = (String -> FieldName
Core.FieldName String
"description")

_InterfaceTypeDefinition_Sequence_name :: FieldName
_InterfaceTypeDefinition_Sequence_name = (String -> FieldName
Core.FieldName String
"name")

_InterfaceTypeDefinition_Sequence_implementsInterfaces :: FieldName
_InterfaceTypeDefinition_Sequence_implementsInterfaces = (String -> FieldName
Core.FieldName String
"implementsInterfaces")

_InterfaceTypeDefinition_Sequence_directives :: FieldName
_InterfaceTypeDefinition_Sequence_directives = (String -> FieldName
Core.FieldName String
"directives")

_InterfaceTypeDefinition_Sequence_fieldsDefinition :: FieldName
_InterfaceTypeDefinition_Sequence_fieldsDefinition = (String -> FieldName
Core.FieldName String
"fieldsDefinition")

data InterfaceTypeDefinition_Sequence2 = 
  InterfaceTypeDefinition_Sequence2 {
    InterfaceTypeDefinition_Sequence2 -> Maybe Description
interfaceTypeDefinition_Sequence2Description :: (Maybe Description),
    InterfaceTypeDefinition_Sequence2 -> Name
interfaceTypeDefinition_Sequence2Name :: Name,
    InterfaceTypeDefinition_Sequence2 -> ImplementsInterfaces
interfaceTypeDefinition_Sequence2ImplementsInterfaces :: ImplementsInterfaces,
    InterfaceTypeDefinition_Sequence2 -> Maybe Directives
interfaceTypeDefinition_Sequence2Directives :: (Maybe Directives)}
  deriving (InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
$c/= :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
== :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
$c== :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
Eq, Eq InterfaceTypeDefinition_Sequence2
InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Ordering
InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
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
min :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
$cmin :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
max :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
$cmax :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
>= :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
$c>= :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
> :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
$c> :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
<= :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
$c<= :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
< :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
$c< :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
compare :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Ordering
$ccompare :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Ordering
Ord, ReadPrec [InterfaceTypeDefinition_Sequence2]
ReadPrec InterfaceTypeDefinition_Sequence2
Int -> ReadS InterfaceTypeDefinition_Sequence2
ReadS [InterfaceTypeDefinition_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceTypeDefinition_Sequence2]
$creadListPrec :: ReadPrec [InterfaceTypeDefinition_Sequence2]
readPrec :: ReadPrec InterfaceTypeDefinition_Sequence2
$creadPrec :: ReadPrec InterfaceTypeDefinition_Sequence2
readList :: ReadS [InterfaceTypeDefinition_Sequence2]
$creadList :: ReadS [InterfaceTypeDefinition_Sequence2]
readsPrec :: Int -> ReadS InterfaceTypeDefinition_Sequence2
$creadsPrec :: Int -> ReadS InterfaceTypeDefinition_Sequence2
Read, Int -> InterfaceTypeDefinition_Sequence2 -> String -> String
[InterfaceTypeDefinition_Sequence2] -> String -> String
InterfaceTypeDefinition_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceTypeDefinition_Sequence2] -> String -> String
$cshowList :: [InterfaceTypeDefinition_Sequence2] -> String -> String
show :: InterfaceTypeDefinition_Sequence2 -> String
$cshow :: InterfaceTypeDefinition_Sequence2 -> String
showsPrec :: Int -> InterfaceTypeDefinition_Sequence2 -> String -> String
$cshowsPrec :: Int -> InterfaceTypeDefinition_Sequence2 -> String -> String
Show)

_InterfaceTypeDefinition_Sequence2 :: Name
_InterfaceTypeDefinition_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InterfaceTypeDefinition.Sequence2")

_InterfaceTypeDefinition_Sequence2_description :: FieldName
_InterfaceTypeDefinition_Sequence2_description = (String -> FieldName
Core.FieldName String
"description")

_InterfaceTypeDefinition_Sequence2_name :: FieldName
_InterfaceTypeDefinition_Sequence2_name = (String -> FieldName
Core.FieldName String
"name")

_InterfaceTypeDefinition_Sequence2_implementsInterfaces :: FieldName
_InterfaceTypeDefinition_Sequence2_implementsInterfaces = (String -> FieldName
Core.FieldName String
"implementsInterfaces")

_InterfaceTypeDefinition_Sequence2_directives :: FieldName
_InterfaceTypeDefinition_Sequence2_directives = (String -> FieldName
Core.FieldName String
"directives")

data InterfaceTypeExtension = 
  InterfaceTypeExtensionSequence InterfaceTypeExtension_Sequence |
  InterfaceTypeExtensionSequence2 InterfaceTypeExtension_Sequence2 |
  InterfaceTypeExtensionSequence3 InterfaceTypeExtension_Sequence3
  deriving (InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
$c/= :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
== :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
$c== :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
Eq, Eq InterfaceTypeExtension
InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
InterfaceTypeExtension -> InterfaceTypeExtension -> Ordering
InterfaceTypeExtension
-> InterfaceTypeExtension -> InterfaceTypeExtension
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
min :: InterfaceTypeExtension
-> InterfaceTypeExtension -> InterfaceTypeExtension
$cmin :: InterfaceTypeExtension
-> InterfaceTypeExtension -> InterfaceTypeExtension
max :: InterfaceTypeExtension
-> InterfaceTypeExtension -> InterfaceTypeExtension
$cmax :: InterfaceTypeExtension
-> InterfaceTypeExtension -> InterfaceTypeExtension
>= :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
$c>= :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
> :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
$c> :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
<= :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
$c<= :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
< :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
$c< :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
compare :: InterfaceTypeExtension -> InterfaceTypeExtension -> Ordering
$ccompare :: InterfaceTypeExtension -> InterfaceTypeExtension -> Ordering
Ord, ReadPrec [InterfaceTypeExtension]
ReadPrec InterfaceTypeExtension
Int -> ReadS InterfaceTypeExtension
ReadS [InterfaceTypeExtension]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceTypeExtension]
$creadListPrec :: ReadPrec [InterfaceTypeExtension]
readPrec :: ReadPrec InterfaceTypeExtension
$creadPrec :: ReadPrec InterfaceTypeExtension
readList :: ReadS [InterfaceTypeExtension]
$creadList :: ReadS [InterfaceTypeExtension]
readsPrec :: Int -> ReadS InterfaceTypeExtension
$creadsPrec :: Int -> ReadS InterfaceTypeExtension
Read, Int -> InterfaceTypeExtension -> String -> String
[InterfaceTypeExtension] -> String -> String
InterfaceTypeExtension -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceTypeExtension] -> String -> String
$cshowList :: [InterfaceTypeExtension] -> String -> String
show :: InterfaceTypeExtension -> String
$cshow :: InterfaceTypeExtension -> String
showsPrec :: Int -> InterfaceTypeExtension -> String -> String
$cshowsPrec :: Int -> InterfaceTypeExtension -> String -> String
Show)

_InterfaceTypeExtension :: Name
_InterfaceTypeExtension = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InterfaceTypeExtension")

_InterfaceTypeExtension_sequence :: FieldName
_InterfaceTypeExtension_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_InterfaceTypeExtension_sequence2 :: FieldName
_InterfaceTypeExtension_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

_InterfaceTypeExtension_sequence3 :: FieldName
_InterfaceTypeExtension_sequence3 = (String -> FieldName
Core.FieldName String
"sequence3")

data InterfaceTypeExtension_Sequence = 
  InterfaceTypeExtension_Sequence {
    InterfaceTypeExtension_Sequence -> Name
interfaceTypeExtension_SequenceName :: Name,
    InterfaceTypeExtension_Sequence -> Maybe ImplementsInterfaces
interfaceTypeExtension_SequenceImplementsInterfaces :: (Maybe ImplementsInterfaces),
    InterfaceTypeExtension_Sequence -> Maybe Directives
interfaceTypeExtension_SequenceDirectives :: (Maybe Directives),
    InterfaceTypeExtension_Sequence -> FieldsDefinition
interfaceTypeExtension_SequenceFieldsDefinition :: FieldsDefinition}
  deriving (InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
$c/= :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
== :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
$c== :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
Eq, Eq InterfaceTypeExtension_Sequence
InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Ordering
InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
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
min :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
$cmin :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
max :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
$cmax :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
>= :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
$c>= :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
> :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
$c> :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
<= :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
$c<= :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
< :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
$c< :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
compare :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Ordering
$ccompare :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Ordering
Ord, ReadPrec [InterfaceTypeExtension_Sequence]
ReadPrec InterfaceTypeExtension_Sequence
Int -> ReadS InterfaceTypeExtension_Sequence
ReadS [InterfaceTypeExtension_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceTypeExtension_Sequence]
$creadListPrec :: ReadPrec [InterfaceTypeExtension_Sequence]
readPrec :: ReadPrec InterfaceTypeExtension_Sequence
$creadPrec :: ReadPrec InterfaceTypeExtension_Sequence
readList :: ReadS [InterfaceTypeExtension_Sequence]
$creadList :: ReadS [InterfaceTypeExtension_Sequence]
readsPrec :: Int -> ReadS InterfaceTypeExtension_Sequence
$creadsPrec :: Int -> ReadS InterfaceTypeExtension_Sequence
Read, Int -> InterfaceTypeExtension_Sequence -> String -> String
[InterfaceTypeExtension_Sequence] -> String -> String
InterfaceTypeExtension_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceTypeExtension_Sequence] -> String -> String
$cshowList :: [InterfaceTypeExtension_Sequence] -> String -> String
show :: InterfaceTypeExtension_Sequence -> String
$cshow :: InterfaceTypeExtension_Sequence -> String
showsPrec :: Int -> InterfaceTypeExtension_Sequence -> String -> String
$cshowsPrec :: Int -> InterfaceTypeExtension_Sequence -> String -> String
Show)

_InterfaceTypeExtension_Sequence :: Name
_InterfaceTypeExtension_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InterfaceTypeExtension.Sequence")

_InterfaceTypeExtension_Sequence_name :: FieldName
_InterfaceTypeExtension_Sequence_name = (String -> FieldName
Core.FieldName String
"name")

_InterfaceTypeExtension_Sequence_implementsInterfaces :: FieldName
_InterfaceTypeExtension_Sequence_implementsInterfaces = (String -> FieldName
Core.FieldName String
"implementsInterfaces")

_InterfaceTypeExtension_Sequence_directives :: FieldName
_InterfaceTypeExtension_Sequence_directives = (String -> FieldName
Core.FieldName String
"directives")

_InterfaceTypeExtension_Sequence_fieldsDefinition :: FieldName
_InterfaceTypeExtension_Sequence_fieldsDefinition = (String -> FieldName
Core.FieldName String
"fieldsDefinition")

data InterfaceTypeExtension_Sequence2 = 
  InterfaceTypeExtension_Sequence2 {
    InterfaceTypeExtension_Sequence2 -> Name
interfaceTypeExtension_Sequence2Name :: Name,
    InterfaceTypeExtension_Sequence2 -> Maybe ImplementsInterfaces
interfaceTypeExtension_Sequence2ImplementsInterfaces :: (Maybe ImplementsInterfaces),
    InterfaceTypeExtension_Sequence2 -> Directives
interfaceTypeExtension_Sequence2Directives :: Directives}
  deriving (InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
$c/= :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
== :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
$c== :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
Eq, Eq InterfaceTypeExtension_Sequence2
InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Ordering
InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
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
min :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
$cmin :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
max :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
$cmax :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
>= :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
$c>= :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
> :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
$c> :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
<= :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
$c<= :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
< :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
$c< :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
compare :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Ordering
$ccompare :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Ordering
Ord, ReadPrec [InterfaceTypeExtension_Sequence2]
ReadPrec InterfaceTypeExtension_Sequence2
Int -> ReadS InterfaceTypeExtension_Sequence2
ReadS [InterfaceTypeExtension_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceTypeExtension_Sequence2]
$creadListPrec :: ReadPrec [InterfaceTypeExtension_Sequence2]
readPrec :: ReadPrec InterfaceTypeExtension_Sequence2
$creadPrec :: ReadPrec InterfaceTypeExtension_Sequence2
readList :: ReadS [InterfaceTypeExtension_Sequence2]
$creadList :: ReadS [InterfaceTypeExtension_Sequence2]
readsPrec :: Int -> ReadS InterfaceTypeExtension_Sequence2
$creadsPrec :: Int -> ReadS InterfaceTypeExtension_Sequence2
Read, Int -> InterfaceTypeExtension_Sequence2 -> String -> String
[InterfaceTypeExtension_Sequence2] -> String -> String
InterfaceTypeExtension_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceTypeExtension_Sequence2] -> String -> String
$cshowList :: [InterfaceTypeExtension_Sequence2] -> String -> String
show :: InterfaceTypeExtension_Sequence2 -> String
$cshow :: InterfaceTypeExtension_Sequence2 -> String
showsPrec :: Int -> InterfaceTypeExtension_Sequence2 -> String -> String
$cshowsPrec :: Int -> InterfaceTypeExtension_Sequence2 -> String -> String
Show)

_InterfaceTypeExtension_Sequence2 :: Name
_InterfaceTypeExtension_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InterfaceTypeExtension.Sequence2")

_InterfaceTypeExtension_Sequence2_name :: FieldName
_InterfaceTypeExtension_Sequence2_name = (String -> FieldName
Core.FieldName String
"name")

_InterfaceTypeExtension_Sequence2_implementsInterfaces :: FieldName
_InterfaceTypeExtension_Sequence2_implementsInterfaces = (String -> FieldName
Core.FieldName String
"implementsInterfaces")

_InterfaceTypeExtension_Sequence2_directives :: FieldName
_InterfaceTypeExtension_Sequence2_directives = (String -> FieldName
Core.FieldName String
"directives")

data InterfaceTypeExtension_Sequence3 = 
  InterfaceTypeExtension_Sequence3 {
    InterfaceTypeExtension_Sequence3 -> Name
interfaceTypeExtension_Sequence3Name :: Name,
    InterfaceTypeExtension_Sequence3 -> ImplementsInterfaces
interfaceTypeExtension_Sequence3ImplementsInterfaces :: ImplementsInterfaces}
  deriving (InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
$c/= :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
== :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
$c== :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
Eq, Eq InterfaceTypeExtension_Sequence3
InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Ordering
InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
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
min :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
$cmin :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
max :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
$cmax :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
>= :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
$c>= :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
> :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
$c> :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
<= :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
$c<= :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
< :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
$c< :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
compare :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Ordering
$ccompare :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Ordering
Ord, ReadPrec [InterfaceTypeExtension_Sequence3]
ReadPrec InterfaceTypeExtension_Sequence3
Int -> ReadS InterfaceTypeExtension_Sequence3
ReadS [InterfaceTypeExtension_Sequence3]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InterfaceTypeExtension_Sequence3]
$creadListPrec :: ReadPrec [InterfaceTypeExtension_Sequence3]
readPrec :: ReadPrec InterfaceTypeExtension_Sequence3
$creadPrec :: ReadPrec InterfaceTypeExtension_Sequence3
readList :: ReadS [InterfaceTypeExtension_Sequence3]
$creadList :: ReadS [InterfaceTypeExtension_Sequence3]
readsPrec :: Int -> ReadS InterfaceTypeExtension_Sequence3
$creadsPrec :: Int -> ReadS InterfaceTypeExtension_Sequence3
Read, Int -> InterfaceTypeExtension_Sequence3 -> String -> String
[InterfaceTypeExtension_Sequence3] -> String -> String
InterfaceTypeExtension_Sequence3 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InterfaceTypeExtension_Sequence3] -> String -> String
$cshowList :: [InterfaceTypeExtension_Sequence3] -> String -> String
show :: InterfaceTypeExtension_Sequence3 -> String
$cshow :: InterfaceTypeExtension_Sequence3 -> String
showsPrec :: Int -> InterfaceTypeExtension_Sequence3 -> String -> String
$cshowsPrec :: Int -> InterfaceTypeExtension_Sequence3 -> String -> String
Show)

_InterfaceTypeExtension_Sequence3 :: Name
_InterfaceTypeExtension_Sequence3 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InterfaceTypeExtension.Sequence3")

_InterfaceTypeExtension_Sequence3_name :: FieldName
_InterfaceTypeExtension_Sequence3_name = (String -> FieldName
Core.FieldName String
"name")

_InterfaceTypeExtension_Sequence3_implementsInterfaces :: FieldName
_InterfaceTypeExtension_Sequence3_implementsInterfaces = (String -> FieldName
Core.FieldName String
"implementsInterfaces")

data UnionTypeDefinition = 
  UnionTypeDefinition {
    UnionTypeDefinition -> Maybe Description
unionTypeDefinitionDescription :: (Maybe Description),
    UnionTypeDefinition -> Name
unionTypeDefinitionName :: Name,
    UnionTypeDefinition -> Maybe Directives
unionTypeDefinitionDirectives :: (Maybe Directives),
    UnionTypeDefinition -> Maybe UnionMemberTypes
unionTypeDefinitionUnionMemberTypes :: (Maybe UnionMemberTypes)}
  deriving (UnionTypeDefinition -> UnionTypeDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
$c/= :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
== :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
$c== :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
Eq, Eq UnionTypeDefinition
UnionTypeDefinition -> UnionTypeDefinition -> Bool
UnionTypeDefinition -> UnionTypeDefinition -> Ordering
UnionTypeDefinition -> UnionTypeDefinition -> UnionTypeDefinition
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
min :: UnionTypeDefinition -> UnionTypeDefinition -> UnionTypeDefinition
$cmin :: UnionTypeDefinition -> UnionTypeDefinition -> UnionTypeDefinition
max :: UnionTypeDefinition -> UnionTypeDefinition -> UnionTypeDefinition
$cmax :: UnionTypeDefinition -> UnionTypeDefinition -> UnionTypeDefinition
>= :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
$c>= :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
> :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
$c> :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
<= :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
$c<= :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
< :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
$c< :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
compare :: UnionTypeDefinition -> UnionTypeDefinition -> Ordering
$ccompare :: UnionTypeDefinition -> UnionTypeDefinition -> Ordering
Ord, ReadPrec [UnionTypeDefinition]
ReadPrec UnionTypeDefinition
Int -> ReadS UnionTypeDefinition
ReadS [UnionTypeDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnionTypeDefinition]
$creadListPrec :: ReadPrec [UnionTypeDefinition]
readPrec :: ReadPrec UnionTypeDefinition
$creadPrec :: ReadPrec UnionTypeDefinition
readList :: ReadS [UnionTypeDefinition]
$creadList :: ReadS [UnionTypeDefinition]
readsPrec :: Int -> ReadS UnionTypeDefinition
$creadsPrec :: Int -> ReadS UnionTypeDefinition
Read, Int -> UnionTypeDefinition -> String -> String
[UnionTypeDefinition] -> String -> String
UnionTypeDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UnionTypeDefinition] -> String -> String
$cshowList :: [UnionTypeDefinition] -> String -> String
show :: UnionTypeDefinition -> String
$cshow :: UnionTypeDefinition -> String
showsPrec :: Int -> UnionTypeDefinition -> String -> String
$cshowsPrec :: Int -> UnionTypeDefinition -> String -> String
Show)

_UnionTypeDefinition :: Name
_UnionTypeDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.UnionTypeDefinition")

_UnionTypeDefinition_description :: FieldName
_UnionTypeDefinition_description = (String -> FieldName
Core.FieldName String
"description")

_UnionTypeDefinition_name :: FieldName
_UnionTypeDefinition_name = (String -> FieldName
Core.FieldName String
"name")

_UnionTypeDefinition_directives :: FieldName
_UnionTypeDefinition_directives = (String -> FieldName
Core.FieldName String
"directives")

_UnionTypeDefinition_unionMemberTypes :: FieldName
_UnionTypeDefinition_unionMemberTypes = (String -> FieldName
Core.FieldName String
"unionMemberTypes")

data UnionMemberTypes = 
  UnionMemberTypesSequence UnionMemberTypes_Sequence |
  UnionMemberTypesSequence2 UnionMemberTypes_Sequence2
  deriving (UnionMemberTypes -> UnionMemberTypes -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnionMemberTypes -> UnionMemberTypes -> Bool
$c/= :: UnionMemberTypes -> UnionMemberTypes -> Bool
== :: UnionMemberTypes -> UnionMemberTypes -> Bool
$c== :: UnionMemberTypes -> UnionMemberTypes -> Bool
Eq, Eq UnionMemberTypes
UnionMemberTypes -> UnionMemberTypes -> Bool
UnionMemberTypes -> UnionMemberTypes -> Ordering
UnionMemberTypes -> UnionMemberTypes -> UnionMemberTypes
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
min :: UnionMemberTypes -> UnionMemberTypes -> UnionMemberTypes
$cmin :: UnionMemberTypes -> UnionMemberTypes -> UnionMemberTypes
max :: UnionMemberTypes -> UnionMemberTypes -> UnionMemberTypes
$cmax :: UnionMemberTypes -> UnionMemberTypes -> UnionMemberTypes
>= :: UnionMemberTypes -> UnionMemberTypes -> Bool
$c>= :: UnionMemberTypes -> UnionMemberTypes -> Bool
> :: UnionMemberTypes -> UnionMemberTypes -> Bool
$c> :: UnionMemberTypes -> UnionMemberTypes -> Bool
<= :: UnionMemberTypes -> UnionMemberTypes -> Bool
$c<= :: UnionMemberTypes -> UnionMemberTypes -> Bool
< :: UnionMemberTypes -> UnionMemberTypes -> Bool
$c< :: UnionMemberTypes -> UnionMemberTypes -> Bool
compare :: UnionMemberTypes -> UnionMemberTypes -> Ordering
$ccompare :: UnionMemberTypes -> UnionMemberTypes -> Ordering
Ord, ReadPrec [UnionMemberTypes]
ReadPrec UnionMemberTypes
Int -> ReadS UnionMemberTypes
ReadS [UnionMemberTypes]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnionMemberTypes]
$creadListPrec :: ReadPrec [UnionMemberTypes]
readPrec :: ReadPrec UnionMemberTypes
$creadPrec :: ReadPrec UnionMemberTypes
readList :: ReadS [UnionMemberTypes]
$creadList :: ReadS [UnionMemberTypes]
readsPrec :: Int -> ReadS UnionMemberTypes
$creadsPrec :: Int -> ReadS UnionMemberTypes
Read, Int -> UnionMemberTypes -> String -> String
[UnionMemberTypes] -> String -> String
UnionMemberTypes -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UnionMemberTypes] -> String -> String
$cshowList :: [UnionMemberTypes] -> String -> String
show :: UnionMemberTypes -> String
$cshow :: UnionMemberTypes -> String
showsPrec :: Int -> UnionMemberTypes -> String -> String
$cshowsPrec :: Int -> UnionMemberTypes -> String -> String
Show)

_UnionMemberTypes :: Name
_UnionMemberTypes = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.UnionMemberTypes")

_UnionMemberTypes_sequence :: FieldName
_UnionMemberTypes_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_UnionMemberTypes_sequence2 :: FieldName
_UnionMemberTypes_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data UnionMemberTypes_Sequence = 
  UnionMemberTypes_Sequence {
    UnionMemberTypes_Sequence -> UnionMemberTypes
unionMemberTypes_SequenceUnionMemberTypes :: UnionMemberTypes,
    UnionMemberTypes_Sequence -> NamedType
unionMemberTypes_SequenceNamedType :: NamedType}
  deriving (UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
$c/= :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
== :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
$c== :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
Eq, Eq UnionMemberTypes_Sequence
UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Ordering
UnionMemberTypes_Sequence
-> UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence
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
min :: UnionMemberTypes_Sequence
-> UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence
$cmin :: UnionMemberTypes_Sequence
-> UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence
max :: UnionMemberTypes_Sequence
-> UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence
$cmax :: UnionMemberTypes_Sequence
-> UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence
>= :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
$c>= :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
> :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
$c> :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
<= :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
$c<= :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
< :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
$c< :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
compare :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Ordering
$ccompare :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Ordering
Ord, ReadPrec [UnionMemberTypes_Sequence]
ReadPrec UnionMemberTypes_Sequence
Int -> ReadS UnionMemberTypes_Sequence
ReadS [UnionMemberTypes_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnionMemberTypes_Sequence]
$creadListPrec :: ReadPrec [UnionMemberTypes_Sequence]
readPrec :: ReadPrec UnionMemberTypes_Sequence
$creadPrec :: ReadPrec UnionMemberTypes_Sequence
readList :: ReadS [UnionMemberTypes_Sequence]
$creadList :: ReadS [UnionMemberTypes_Sequence]
readsPrec :: Int -> ReadS UnionMemberTypes_Sequence
$creadsPrec :: Int -> ReadS UnionMemberTypes_Sequence
Read, Int -> UnionMemberTypes_Sequence -> String -> String
[UnionMemberTypes_Sequence] -> String -> String
UnionMemberTypes_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UnionMemberTypes_Sequence] -> String -> String
$cshowList :: [UnionMemberTypes_Sequence] -> String -> String
show :: UnionMemberTypes_Sequence -> String
$cshow :: UnionMemberTypes_Sequence -> String
showsPrec :: Int -> UnionMemberTypes_Sequence -> String -> String
$cshowsPrec :: Int -> UnionMemberTypes_Sequence -> String -> String
Show)

_UnionMemberTypes_Sequence :: Name
_UnionMemberTypes_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.UnionMemberTypes.Sequence")

_UnionMemberTypes_Sequence_unionMemberTypes :: FieldName
_UnionMemberTypes_Sequence_unionMemberTypes = (String -> FieldName
Core.FieldName String
"unionMemberTypes")

_UnionMemberTypes_Sequence_namedType :: FieldName
_UnionMemberTypes_Sequence_namedType = (String -> FieldName
Core.FieldName String
"namedType")

data UnionMemberTypes_Sequence2 = 
  UnionMemberTypes_Sequence2 {
    UnionMemberTypes_Sequence2 -> Maybe ()
unionMemberTypes_Sequence2Or :: (Maybe ()),
    UnionMemberTypes_Sequence2 -> NamedType
unionMemberTypes_Sequence2NamedType :: NamedType}
  deriving (UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
$c/= :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
== :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
$c== :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
Eq, Eq UnionMemberTypes_Sequence2
UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> Ordering
UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2
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
min :: UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2
$cmin :: UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2
max :: UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2
$cmax :: UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2
>= :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
$c>= :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
> :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
$c> :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
<= :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
$c<= :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
< :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
$c< :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
compare :: UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> Ordering
$ccompare :: UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> Ordering
Ord, ReadPrec [UnionMemberTypes_Sequence2]
ReadPrec UnionMemberTypes_Sequence2
Int -> ReadS UnionMemberTypes_Sequence2
ReadS [UnionMemberTypes_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnionMemberTypes_Sequence2]
$creadListPrec :: ReadPrec [UnionMemberTypes_Sequence2]
readPrec :: ReadPrec UnionMemberTypes_Sequence2
$creadPrec :: ReadPrec UnionMemberTypes_Sequence2
readList :: ReadS [UnionMemberTypes_Sequence2]
$creadList :: ReadS [UnionMemberTypes_Sequence2]
readsPrec :: Int -> ReadS UnionMemberTypes_Sequence2
$creadsPrec :: Int -> ReadS UnionMemberTypes_Sequence2
Read, Int -> UnionMemberTypes_Sequence2 -> String -> String
[UnionMemberTypes_Sequence2] -> String -> String
UnionMemberTypes_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UnionMemberTypes_Sequence2] -> String -> String
$cshowList :: [UnionMemberTypes_Sequence2] -> String -> String
show :: UnionMemberTypes_Sequence2 -> String
$cshow :: UnionMemberTypes_Sequence2 -> String
showsPrec :: Int -> UnionMemberTypes_Sequence2 -> String -> String
$cshowsPrec :: Int -> UnionMemberTypes_Sequence2 -> String -> String
Show)

_UnionMemberTypes_Sequence2 :: Name
_UnionMemberTypes_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.UnionMemberTypes.Sequence2")

_UnionMemberTypes_Sequence2_or :: FieldName
_UnionMemberTypes_Sequence2_or = (String -> FieldName
Core.FieldName String
"or")

_UnionMemberTypes_Sequence2_namedType :: FieldName
_UnionMemberTypes_Sequence2_namedType = (String -> FieldName
Core.FieldName String
"namedType")

data UnionTypeExtension = 
  UnionTypeExtensionSequence UnionTypeExtension_Sequence |
  UnionTypeExtensionSequence2 UnionTypeExtension_Sequence2
  deriving (UnionTypeExtension -> UnionTypeExtension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnionTypeExtension -> UnionTypeExtension -> Bool
$c/= :: UnionTypeExtension -> UnionTypeExtension -> Bool
== :: UnionTypeExtension -> UnionTypeExtension -> Bool
$c== :: UnionTypeExtension -> UnionTypeExtension -> Bool
Eq, Eq UnionTypeExtension
UnionTypeExtension -> UnionTypeExtension -> Bool
UnionTypeExtension -> UnionTypeExtension -> Ordering
UnionTypeExtension -> UnionTypeExtension -> UnionTypeExtension
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
min :: UnionTypeExtension -> UnionTypeExtension -> UnionTypeExtension
$cmin :: UnionTypeExtension -> UnionTypeExtension -> UnionTypeExtension
max :: UnionTypeExtension -> UnionTypeExtension -> UnionTypeExtension
$cmax :: UnionTypeExtension -> UnionTypeExtension -> UnionTypeExtension
>= :: UnionTypeExtension -> UnionTypeExtension -> Bool
$c>= :: UnionTypeExtension -> UnionTypeExtension -> Bool
> :: UnionTypeExtension -> UnionTypeExtension -> Bool
$c> :: UnionTypeExtension -> UnionTypeExtension -> Bool
<= :: UnionTypeExtension -> UnionTypeExtension -> Bool
$c<= :: UnionTypeExtension -> UnionTypeExtension -> Bool
< :: UnionTypeExtension -> UnionTypeExtension -> Bool
$c< :: UnionTypeExtension -> UnionTypeExtension -> Bool
compare :: UnionTypeExtension -> UnionTypeExtension -> Ordering
$ccompare :: UnionTypeExtension -> UnionTypeExtension -> Ordering
Ord, ReadPrec [UnionTypeExtension]
ReadPrec UnionTypeExtension
Int -> ReadS UnionTypeExtension
ReadS [UnionTypeExtension]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnionTypeExtension]
$creadListPrec :: ReadPrec [UnionTypeExtension]
readPrec :: ReadPrec UnionTypeExtension
$creadPrec :: ReadPrec UnionTypeExtension
readList :: ReadS [UnionTypeExtension]
$creadList :: ReadS [UnionTypeExtension]
readsPrec :: Int -> ReadS UnionTypeExtension
$creadsPrec :: Int -> ReadS UnionTypeExtension
Read, Int -> UnionTypeExtension -> String -> String
[UnionTypeExtension] -> String -> String
UnionTypeExtension -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UnionTypeExtension] -> String -> String
$cshowList :: [UnionTypeExtension] -> String -> String
show :: UnionTypeExtension -> String
$cshow :: UnionTypeExtension -> String
showsPrec :: Int -> UnionTypeExtension -> String -> String
$cshowsPrec :: Int -> UnionTypeExtension -> String -> String
Show)

_UnionTypeExtension :: Name
_UnionTypeExtension = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.UnionTypeExtension")

_UnionTypeExtension_sequence :: FieldName
_UnionTypeExtension_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_UnionTypeExtension_sequence2 :: FieldName
_UnionTypeExtension_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data UnionTypeExtension_Sequence = 
  UnionTypeExtension_Sequence {
    UnionTypeExtension_Sequence -> Name
unionTypeExtension_SequenceName :: Name,
    UnionTypeExtension_Sequence -> Maybe Directives
unionTypeExtension_SequenceDirectives :: (Maybe Directives),
    UnionTypeExtension_Sequence -> UnionMemberTypes
unionTypeExtension_SequenceUnionMemberTypes :: UnionMemberTypes}
  deriving (UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
$c/= :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
== :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
$c== :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
Eq, Eq UnionTypeExtension_Sequence
UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> Ordering
UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence
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
min :: UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence
$cmin :: UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence
max :: UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence
$cmax :: UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence
>= :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
$c>= :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
> :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
$c> :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
<= :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
$c<= :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
< :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
$c< :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
compare :: UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> Ordering
$ccompare :: UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> Ordering
Ord, ReadPrec [UnionTypeExtension_Sequence]
ReadPrec UnionTypeExtension_Sequence
Int -> ReadS UnionTypeExtension_Sequence
ReadS [UnionTypeExtension_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnionTypeExtension_Sequence]
$creadListPrec :: ReadPrec [UnionTypeExtension_Sequence]
readPrec :: ReadPrec UnionTypeExtension_Sequence
$creadPrec :: ReadPrec UnionTypeExtension_Sequence
readList :: ReadS [UnionTypeExtension_Sequence]
$creadList :: ReadS [UnionTypeExtension_Sequence]
readsPrec :: Int -> ReadS UnionTypeExtension_Sequence
$creadsPrec :: Int -> ReadS UnionTypeExtension_Sequence
Read, Int -> UnionTypeExtension_Sequence -> String -> String
[UnionTypeExtension_Sequence] -> String -> String
UnionTypeExtension_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UnionTypeExtension_Sequence] -> String -> String
$cshowList :: [UnionTypeExtension_Sequence] -> String -> String
show :: UnionTypeExtension_Sequence -> String
$cshow :: UnionTypeExtension_Sequence -> String
showsPrec :: Int -> UnionTypeExtension_Sequence -> String -> String
$cshowsPrec :: Int -> UnionTypeExtension_Sequence -> String -> String
Show)

_UnionTypeExtension_Sequence :: Name
_UnionTypeExtension_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.UnionTypeExtension.Sequence")

_UnionTypeExtension_Sequence_name :: FieldName
_UnionTypeExtension_Sequence_name = (String -> FieldName
Core.FieldName String
"name")

_UnionTypeExtension_Sequence_directives :: FieldName
_UnionTypeExtension_Sequence_directives = (String -> FieldName
Core.FieldName String
"directives")

_UnionTypeExtension_Sequence_unionMemberTypes :: FieldName
_UnionTypeExtension_Sequence_unionMemberTypes = (String -> FieldName
Core.FieldName String
"unionMemberTypes")

data UnionTypeExtension_Sequence2 = 
  UnionTypeExtension_Sequence2 {
    UnionTypeExtension_Sequence2 -> Name
unionTypeExtension_Sequence2Name :: Name,
    UnionTypeExtension_Sequence2 -> Directives
unionTypeExtension_Sequence2Directives :: Directives}
  deriving (UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
$c/= :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
== :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
$c== :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
Eq, Eq UnionTypeExtension_Sequence2
UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Ordering
UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> UnionTypeExtension_Sequence2
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
min :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> UnionTypeExtension_Sequence2
$cmin :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> UnionTypeExtension_Sequence2
max :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> UnionTypeExtension_Sequence2
$cmax :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> UnionTypeExtension_Sequence2
>= :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
$c>= :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
> :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
$c> :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
<= :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
$c<= :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
< :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
$c< :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
compare :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Ordering
$ccompare :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Ordering
Ord, ReadPrec [UnionTypeExtension_Sequence2]
ReadPrec UnionTypeExtension_Sequence2
Int -> ReadS UnionTypeExtension_Sequence2
ReadS [UnionTypeExtension_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [UnionTypeExtension_Sequence2]
$creadListPrec :: ReadPrec [UnionTypeExtension_Sequence2]
readPrec :: ReadPrec UnionTypeExtension_Sequence2
$creadPrec :: ReadPrec UnionTypeExtension_Sequence2
readList :: ReadS [UnionTypeExtension_Sequence2]
$creadList :: ReadS [UnionTypeExtension_Sequence2]
readsPrec :: Int -> ReadS UnionTypeExtension_Sequence2
$creadsPrec :: Int -> ReadS UnionTypeExtension_Sequence2
Read, Int -> UnionTypeExtension_Sequence2 -> String -> String
[UnionTypeExtension_Sequence2] -> String -> String
UnionTypeExtension_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [UnionTypeExtension_Sequence2] -> String -> String
$cshowList :: [UnionTypeExtension_Sequence2] -> String -> String
show :: UnionTypeExtension_Sequence2 -> String
$cshow :: UnionTypeExtension_Sequence2 -> String
showsPrec :: Int -> UnionTypeExtension_Sequence2 -> String -> String
$cshowsPrec :: Int -> UnionTypeExtension_Sequence2 -> String -> String
Show)

_UnionTypeExtension_Sequence2 :: Name
_UnionTypeExtension_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.UnionTypeExtension.Sequence2")

_UnionTypeExtension_Sequence2_name :: FieldName
_UnionTypeExtension_Sequence2_name = (String -> FieldName
Core.FieldName String
"name")

_UnionTypeExtension_Sequence2_directives :: FieldName
_UnionTypeExtension_Sequence2_directives = (String -> FieldName
Core.FieldName String
"directives")

data EnumTypeDefinition = 
  EnumTypeDefinitionSequence EnumTypeDefinition_Sequence |
  EnumTypeDefinitionSequence2 EnumTypeDefinition_Sequence2
  deriving (EnumTypeDefinition -> EnumTypeDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
$c/= :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
== :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
$c== :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
Eq, Eq EnumTypeDefinition
EnumTypeDefinition -> EnumTypeDefinition -> Bool
EnumTypeDefinition -> EnumTypeDefinition -> Ordering
EnumTypeDefinition -> EnumTypeDefinition -> EnumTypeDefinition
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
min :: EnumTypeDefinition -> EnumTypeDefinition -> EnumTypeDefinition
$cmin :: EnumTypeDefinition -> EnumTypeDefinition -> EnumTypeDefinition
max :: EnumTypeDefinition -> EnumTypeDefinition -> EnumTypeDefinition
$cmax :: EnumTypeDefinition -> EnumTypeDefinition -> EnumTypeDefinition
>= :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
$c>= :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
> :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
$c> :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
<= :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
$c<= :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
< :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
$c< :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
compare :: EnumTypeDefinition -> EnumTypeDefinition -> Ordering
$ccompare :: EnumTypeDefinition -> EnumTypeDefinition -> Ordering
Ord, ReadPrec [EnumTypeDefinition]
ReadPrec EnumTypeDefinition
Int -> ReadS EnumTypeDefinition
ReadS [EnumTypeDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumTypeDefinition]
$creadListPrec :: ReadPrec [EnumTypeDefinition]
readPrec :: ReadPrec EnumTypeDefinition
$creadPrec :: ReadPrec EnumTypeDefinition
readList :: ReadS [EnumTypeDefinition]
$creadList :: ReadS [EnumTypeDefinition]
readsPrec :: Int -> ReadS EnumTypeDefinition
$creadsPrec :: Int -> ReadS EnumTypeDefinition
Read, Int -> EnumTypeDefinition -> String -> String
[EnumTypeDefinition] -> String -> String
EnumTypeDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumTypeDefinition] -> String -> String
$cshowList :: [EnumTypeDefinition] -> String -> String
show :: EnumTypeDefinition -> String
$cshow :: EnumTypeDefinition -> String
showsPrec :: Int -> EnumTypeDefinition -> String -> String
$cshowsPrec :: Int -> EnumTypeDefinition -> String -> String
Show)

_EnumTypeDefinition :: Name
_EnumTypeDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.EnumTypeDefinition")

_EnumTypeDefinition_sequence :: FieldName
_EnumTypeDefinition_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_EnumTypeDefinition_sequence2 :: FieldName
_EnumTypeDefinition_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data EnumTypeDefinition_Sequence = 
  EnumTypeDefinition_Sequence {
    EnumTypeDefinition_Sequence -> Maybe Description
enumTypeDefinition_SequenceDescription :: (Maybe Description),
    EnumTypeDefinition_Sequence -> Name
enumTypeDefinition_SequenceName :: Name,
    EnumTypeDefinition_Sequence -> Maybe Directives
enumTypeDefinition_SequenceDirectives :: (Maybe Directives),
    EnumTypeDefinition_Sequence -> EnumValuesDefinition
enumTypeDefinition_SequenceEnumValuesDefinition :: EnumValuesDefinition}
  deriving (EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
$c/= :: EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
== :: EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
$c== :: EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
Eq, Eq EnumTypeDefinition_Sequence
EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
EnumTypeDefinition_Sequence
-> EnumTypeDefinition_Sequence -> Ordering
EnumTypeDefinition_Sequence
-> EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence
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
min :: EnumTypeDefinition_Sequence
-> EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence
$cmin :: EnumTypeDefinition_Sequence
-> EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence
max :: EnumTypeDefinition_Sequence
-> EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence
$cmax :: EnumTypeDefinition_Sequence
-> EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence
>= :: EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
$c>= :: EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
> :: EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
$c> :: EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
<= :: EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
$c<= :: EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
< :: EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
$c< :: EnumTypeDefinition_Sequence -> EnumTypeDefinition_Sequence -> Bool
compare :: EnumTypeDefinition_Sequence
-> EnumTypeDefinition_Sequence -> Ordering
$ccompare :: EnumTypeDefinition_Sequence
-> EnumTypeDefinition_Sequence -> Ordering
Ord, ReadPrec [EnumTypeDefinition_Sequence]
ReadPrec EnumTypeDefinition_Sequence
Int -> ReadS EnumTypeDefinition_Sequence
ReadS [EnumTypeDefinition_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumTypeDefinition_Sequence]
$creadListPrec :: ReadPrec [EnumTypeDefinition_Sequence]
readPrec :: ReadPrec EnumTypeDefinition_Sequence
$creadPrec :: ReadPrec EnumTypeDefinition_Sequence
readList :: ReadS [EnumTypeDefinition_Sequence]
$creadList :: ReadS [EnumTypeDefinition_Sequence]
readsPrec :: Int -> ReadS EnumTypeDefinition_Sequence
$creadsPrec :: Int -> ReadS EnumTypeDefinition_Sequence
Read, Int -> EnumTypeDefinition_Sequence -> String -> String
[EnumTypeDefinition_Sequence] -> String -> String
EnumTypeDefinition_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumTypeDefinition_Sequence] -> String -> String
$cshowList :: [EnumTypeDefinition_Sequence] -> String -> String
show :: EnumTypeDefinition_Sequence -> String
$cshow :: EnumTypeDefinition_Sequence -> String
showsPrec :: Int -> EnumTypeDefinition_Sequence -> String -> String
$cshowsPrec :: Int -> EnumTypeDefinition_Sequence -> String -> String
Show)

_EnumTypeDefinition_Sequence :: Name
_EnumTypeDefinition_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.EnumTypeDefinition.Sequence")

_EnumTypeDefinition_Sequence_description :: FieldName
_EnumTypeDefinition_Sequence_description = (String -> FieldName
Core.FieldName String
"description")

_EnumTypeDefinition_Sequence_name :: FieldName
_EnumTypeDefinition_Sequence_name = (String -> FieldName
Core.FieldName String
"name")

_EnumTypeDefinition_Sequence_directives :: FieldName
_EnumTypeDefinition_Sequence_directives = (String -> FieldName
Core.FieldName String
"directives")

_EnumTypeDefinition_Sequence_enumValuesDefinition :: FieldName
_EnumTypeDefinition_Sequence_enumValuesDefinition = (String -> FieldName
Core.FieldName String
"enumValuesDefinition")

data EnumTypeDefinition_Sequence2 = 
  EnumTypeDefinition_Sequence2 {
    EnumTypeDefinition_Sequence2 -> Maybe Description
enumTypeDefinition_Sequence2Description :: (Maybe Description),
    EnumTypeDefinition_Sequence2 -> Maybe Directives
enumTypeDefinition_Sequence2Directives :: (Maybe Directives)}
  deriving (EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
$c/= :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
== :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
$c== :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
Eq, Eq EnumTypeDefinition_Sequence2
EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Ordering
EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> EnumTypeDefinition_Sequence2
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
min :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> EnumTypeDefinition_Sequence2
$cmin :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> EnumTypeDefinition_Sequence2
max :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> EnumTypeDefinition_Sequence2
$cmax :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> EnumTypeDefinition_Sequence2
>= :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
$c>= :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
> :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
$c> :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
<= :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
$c<= :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
< :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
$c< :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Bool
compare :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Ordering
$ccompare :: EnumTypeDefinition_Sequence2
-> EnumTypeDefinition_Sequence2 -> Ordering
Ord, ReadPrec [EnumTypeDefinition_Sequence2]
ReadPrec EnumTypeDefinition_Sequence2
Int -> ReadS EnumTypeDefinition_Sequence2
ReadS [EnumTypeDefinition_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumTypeDefinition_Sequence2]
$creadListPrec :: ReadPrec [EnumTypeDefinition_Sequence2]
readPrec :: ReadPrec EnumTypeDefinition_Sequence2
$creadPrec :: ReadPrec EnumTypeDefinition_Sequence2
readList :: ReadS [EnumTypeDefinition_Sequence2]
$creadList :: ReadS [EnumTypeDefinition_Sequence2]
readsPrec :: Int -> ReadS EnumTypeDefinition_Sequence2
$creadsPrec :: Int -> ReadS EnumTypeDefinition_Sequence2
Read, Int -> EnumTypeDefinition_Sequence2 -> String -> String
[EnumTypeDefinition_Sequence2] -> String -> String
EnumTypeDefinition_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumTypeDefinition_Sequence2] -> String -> String
$cshowList :: [EnumTypeDefinition_Sequence2] -> String -> String
show :: EnumTypeDefinition_Sequence2 -> String
$cshow :: EnumTypeDefinition_Sequence2 -> String
showsPrec :: Int -> EnumTypeDefinition_Sequence2 -> String -> String
$cshowsPrec :: Int -> EnumTypeDefinition_Sequence2 -> String -> String
Show)

_EnumTypeDefinition_Sequence2 :: Name
_EnumTypeDefinition_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.EnumTypeDefinition.Sequence2")

_EnumTypeDefinition_Sequence2_description :: FieldName
_EnumTypeDefinition_Sequence2_description = (String -> FieldName
Core.FieldName String
"description")

_EnumTypeDefinition_Sequence2_directives :: FieldName
_EnumTypeDefinition_Sequence2_directives = (String -> FieldName
Core.FieldName String
"directives")

data EnumValuesDefinition = 
  EnumValuesDefinition {
    EnumValuesDefinition -> [EnumValueDefinition]
enumValuesDefinitionListOfEnumValueDefinition :: [EnumValueDefinition]}
  deriving (EnumValuesDefinition -> EnumValuesDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
$c/= :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
== :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
$c== :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
Eq, Eq EnumValuesDefinition
EnumValuesDefinition -> EnumValuesDefinition -> Bool
EnumValuesDefinition -> EnumValuesDefinition -> Ordering
EnumValuesDefinition
-> EnumValuesDefinition -> EnumValuesDefinition
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
min :: EnumValuesDefinition
-> EnumValuesDefinition -> EnumValuesDefinition
$cmin :: EnumValuesDefinition
-> EnumValuesDefinition -> EnumValuesDefinition
max :: EnumValuesDefinition
-> EnumValuesDefinition -> EnumValuesDefinition
$cmax :: EnumValuesDefinition
-> EnumValuesDefinition -> EnumValuesDefinition
>= :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
$c>= :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
> :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
$c> :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
<= :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
$c<= :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
< :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
$c< :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
compare :: EnumValuesDefinition -> EnumValuesDefinition -> Ordering
$ccompare :: EnumValuesDefinition -> EnumValuesDefinition -> Ordering
Ord, ReadPrec [EnumValuesDefinition]
ReadPrec EnumValuesDefinition
Int -> ReadS EnumValuesDefinition
ReadS [EnumValuesDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumValuesDefinition]
$creadListPrec :: ReadPrec [EnumValuesDefinition]
readPrec :: ReadPrec EnumValuesDefinition
$creadPrec :: ReadPrec EnumValuesDefinition
readList :: ReadS [EnumValuesDefinition]
$creadList :: ReadS [EnumValuesDefinition]
readsPrec :: Int -> ReadS EnumValuesDefinition
$creadsPrec :: Int -> ReadS EnumValuesDefinition
Read, Int -> EnumValuesDefinition -> String -> String
[EnumValuesDefinition] -> String -> String
EnumValuesDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumValuesDefinition] -> String -> String
$cshowList :: [EnumValuesDefinition] -> String -> String
show :: EnumValuesDefinition -> String
$cshow :: EnumValuesDefinition -> String
showsPrec :: Int -> EnumValuesDefinition -> String -> String
$cshowsPrec :: Int -> EnumValuesDefinition -> String -> String
Show)

_EnumValuesDefinition :: Name
_EnumValuesDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.EnumValuesDefinition")

_EnumValuesDefinition_listOfEnumValueDefinition :: FieldName
_EnumValuesDefinition_listOfEnumValueDefinition = (String -> FieldName
Core.FieldName String
"listOfEnumValueDefinition")

data EnumValueDefinition = 
  EnumValueDefinition {
    EnumValueDefinition -> Maybe Description
enumValueDefinitionDescription :: (Maybe Description),
    EnumValueDefinition -> EnumValue
enumValueDefinitionEnumValue :: EnumValue,
    EnumValueDefinition -> Maybe Directives
enumValueDefinitionDirectives :: (Maybe Directives)}
  deriving (EnumValueDefinition -> EnumValueDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumValueDefinition -> EnumValueDefinition -> Bool
$c/= :: EnumValueDefinition -> EnumValueDefinition -> Bool
== :: EnumValueDefinition -> EnumValueDefinition -> Bool
$c== :: EnumValueDefinition -> EnumValueDefinition -> Bool
Eq, Eq EnumValueDefinition
EnumValueDefinition -> EnumValueDefinition -> Bool
EnumValueDefinition -> EnumValueDefinition -> Ordering
EnumValueDefinition -> EnumValueDefinition -> EnumValueDefinition
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
min :: EnumValueDefinition -> EnumValueDefinition -> EnumValueDefinition
$cmin :: EnumValueDefinition -> EnumValueDefinition -> EnumValueDefinition
max :: EnumValueDefinition -> EnumValueDefinition -> EnumValueDefinition
$cmax :: EnumValueDefinition -> EnumValueDefinition -> EnumValueDefinition
>= :: EnumValueDefinition -> EnumValueDefinition -> Bool
$c>= :: EnumValueDefinition -> EnumValueDefinition -> Bool
> :: EnumValueDefinition -> EnumValueDefinition -> Bool
$c> :: EnumValueDefinition -> EnumValueDefinition -> Bool
<= :: EnumValueDefinition -> EnumValueDefinition -> Bool
$c<= :: EnumValueDefinition -> EnumValueDefinition -> Bool
< :: EnumValueDefinition -> EnumValueDefinition -> Bool
$c< :: EnumValueDefinition -> EnumValueDefinition -> Bool
compare :: EnumValueDefinition -> EnumValueDefinition -> Ordering
$ccompare :: EnumValueDefinition -> EnumValueDefinition -> Ordering
Ord, ReadPrec [EnumValueDefinition]
ReadPrec EnumValueDefinition
Int -> ReadS EnumValueDefinition
ReadS [EnumValueDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumValueDefinition]
$creadListPrec :: ReadPrec [EnumValueDefinition]
readPrec :: ReadPrec EnumValueDefinition
$creadPrec :: ReadPrec EnumValueDefinition
readList :: ReadS [EnumValueDefinition]
$creadList :: ReadS [EnumValueDefinition]
readsPrec :: Int -> ReadS EnumValueDefinition
$creadsPrec :: Int -> ReadS EnumValueDefinition
Read, Int -> EnumValueDefinition -> String -> String
[EnumValueDefinition] -> String -> String
EnumValueDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumValueDefinition] -> String -> String
$cshowList :: [EnumValueDefinition] -> String -> String
show :: EnumValueDefinition -> String
$cshow :: EnumValueDefinition -> String
showsPrec :: Int -> EnumValueDefinition -> String -> String
$cshowsPrec :: Int -> EnumValueDefinition -> String -> String
Show)

_EnumValueDefinition :: Name
_EnumValueDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.EnumValueDefinition")

_EnumValueDefinition_description :: FieldName
_EnumValueDefinition_description = (String -> FieldName
Core.FieldName String
"description")

_EnumValueDefinition_enumValue :: FieldName
_EnumValueDefinition_enumValue = (String -> FieldName
Core.FieldName String
"enumValue")

_EnumValueDefinition_directives :: FieldName
_EnumValueDefinition_directives = (String -> FieldName
Core.FieldName String
"directives")

data EnumTypeExtension = 
  EnumTypeExtensionSequence EnumTypeExtension_Sequence |
  EnumTypeExtensionSequence2 EnumTypeExtension_Sequence2
  deriving (EnumTypeExtension -> EnumTypeExtension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumTypeExtension -> EnumTypeExtension -> Bool
$c/= :: EnumTypeExtension -> EnumTypeExtension -> Bool
== :: EnumTypeExtension -> EnumTypeExtension -> Bool
$c== :: EnumTypeExtension -> EnumTypeExtension -> Bool
Eq, Eq EnumTypeExtension
EnumTypeExtension -> EnumTypeExtension -> Bool
EnumTypeExtension -> EnumTypeExtension -> Ordering
EnumTypeExtension -> EnumTypeExtension -> EnumTypeExtension
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
min :: EnumTypeExtension -> EnumTypeExtension -> EnumTypeExtension
$cmin :: EnumTypeExtension -> EnumTypeExtension -> EnumTypeExtension
max :: EnumTypeExtension -> EnumTypeExtension -> EnumTypeExtension
$cmax :: EnumTypeExtension -> EnumTypeExtension -> EnumTypeExtension
>= :: EnumTypeExtension -> EnumTypeExtension -> Bool
$c>= :: EnumTypeExtension -> EnumTypeExtension -> Bool
> :: EnumTypeExtension -> EnumTypeExtension -> Bool
$c> :: EnumTypeExtension -> EnumTypeExtension -> Bool
<= :: EnumTypeExtension -> EnumTypeExtension -> Bool
$c<= :: EnumTypeExtension -> EnumTypeExtension -> Bool
< :: EnumTypeExtension -> EnumTypeExtension -> Bool
$c< :: EnumTypeExtension -> EnumTypeExtension -> Bool
compare :: EnumTypeExtension -> EnumTypeExtension -> Ordering
$ccompare :: EnumTypeExtension -> EnumTypeExtension -> Ordering
Ord, ReadPrec [EnumTypeExtension]
ReadPrec EnumTypeExtension
Int -> ReadS EnumTypeExtension
ReadS [EnumTypeExtension]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumTypeExtension]
$creadListPrec :: ReadPrec [EnumTypeExtension]
readPrec :: ReadPrec EnumTypeExtension
$creadPrec :: ReadPrec EnumTypeExtension
readList :: ReadS [EnumTypeExtension]
$creadList :: ReadS [EnumTypeExtension]
readsPrec :: Int -> ReadS EnumTypeExtension
$creadsPrec :: Int -> ReadS EnumTypeExtension
Read, Int -> EnumTypeExtension -> String -> String
[EnumTypeExtension] -> String -> String
EnumTypeExtension -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumTypeExtension] -> String -> String
$cshowList :: [EnumTypeExtension] -> String -> String
show :: EnumTypeExtension -> String
$cshow :: EnumTypeExtension -> String
showsPrec :: Int -> EnumTypeExtension -> String -> String
$cshowsPrec :: Int -> EnumTypeExtension -> String -> String
Show)

_EnumTypeExtension :: Name
_EnumTypeExtension = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.EnumTypeExtension")

_EnumTypeExtension_sequence :: FieldName
_EnumTypeExtension_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_EnumTypeExtension_sequence2 :: FieldName
_EnumTypeExtension_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data EnumTypeExtension_Sequence = 
  EnumTypeExtension_Sequence {
    EnumTypeExtension_Sequence -> Name
enumTypeExtension_SequenceName :: Name,
    EnumTypeExtension_Sequence -> Maybe Directives
enumTypeExtension_SequenceDirectives :: (Maybe Directives),
    EnumTypeExtension_Sequence -> EnumValuesDefinition
enumTypeExtension_SequenceEnumValuesDefinition :: EnumValuesDefinition}
  deriving (EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
$c/= :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
== :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
$c== :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
Eq, Eq EnumTypeExtension_Sequence
EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> Ordering
EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence
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
min :: EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence
$cmin :: EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence
max :: EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence
$cmax :: EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence
>= :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
$c>= :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
> :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
$c> :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
<= :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
$c<= :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
< :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
$c< :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
compare :: EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> Ordering
$ccompare :: EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> Ordering
Ord, ReadPrec [EnumTypeExtension_Sequence]
ReadPrec EnumTypeExtension_Sequence
Int -> ReadS EnumTypeExtension_Sequence
ReadS [EnumTypeExtension_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumTypeExtension_Sequence]
$creadListPrec :: ReadPrec [EnumTypeExtension_Sequence]
readPrec :: ReadPrec EnumTypeExtension_Sequence
$creadPrec :: ReadPrec EnumTypeExtension_Sequence
readList :: ReadS [EnumTypeExtension_Sequence]
$creadList :: ReadS [EnumTypeExtension_Sequence]
readsPrec :: Int -> ReadS EnumTypeExtension_Sequence
$creadsPrec :: Int -> ReadS EnumTypeExtension_Sequence
Read, Int -> EnumTypeExtension_Sequence -> String -> String
[EnumTypeExtension_Sequence] -> String -> String
EnumTypeExtension_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumTypeExtension_Sequence] -> String -> String
$cshowList :: [EnumTypeExtension_Sequence] -> String -> String
show :: EnumTypeExtension_Sequence -> String
$cshow :: EnumTypeExtension_Sequence -> String
showsPrec :: Int -> EnumTypeExtension_Sequence -> String -> String
$cshowsPrec :: Int -> EnumTypeExtension_Sequence -> String -> String
Show)

_EnumTypeExtension_Sequence :: Name
_EnumTypeExtension_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.EnumTypeExtension.Sequence")

_EnumTypeExtension_Sequence_name :: FieldName
_EnumTypeExtension_Sequence_name = (String -> FieldName
Core.FieldName String
"name")

_EnumTypeExtension_Sequence_directives :: FieldName
_EnumTypeExtension_Sequence_directives = (String -> FieldName
Core.FieldName String
"directives")

_EnumTypeExtension_Sequence_enumValuesDefinition :: FieldName
_EnumTypeExtension_Sequence_enumValuesDefinition = (String -> FieldName
Core.FieldName String
"enumValuesDefinition")

data EnumTypeExtension_Sequence2 = 
  EnumTypeExtension_Sequence2 {
    EnumTypeExtension_Sequence2 -> Name
enumTypeExtension_Sequence2Name :: Name,
    EnumTypeExtension_Sequence2 -> Directives
enumTypeExtension_Sequence2Directives :: Directives}
  deriving (EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
$c/= :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
== :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
$c== :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
Eq, Eq EnumTypeExtension_Sequence2
EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> Ordering
EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2
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
min :: EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2
$cmin :: EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2
max :: EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2
$cmax :: EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2
>= :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
$c>= :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
> :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
$c> :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
<= :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
$c<= :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
< :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
$c< :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
compare :: EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> Ordering
$ccompare :: EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> Ordering
Ord, ReadPrec [EnumTypeExtension_Sequence2]
ReadPrec EnumTypeExtension_Sequence2
Int -> ReadS EnumTypeExtension_Sequence2
ReadS [EnumTypeExtension_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [EnumTypeExtension_Sequence2]
$creadListPrec :: ReadPrec [EnumTypeExtension_Sequence2]
readPrec :: ReadPrec EnumTypeExtension_Sequence2
$creadPrec :: ReadPrec EnumTypeExtension_Sequence2
readList :: ReadS [EnumTypeExtension_Sequence2]
$creadList :: ReadS [EnumTypeExtension_Sequence2]
readsPrec :: Int -> ReadS EnumTypeExtension_Sequence2
$creadsPrec :: Int -> ReadS EnumTypeExtension_Sequence2
Read, Int -> EnumTypeExtension_Sequence2 -> String -> String
[EnumTypeExtension_Sequence2] -> String -> String
EnumTypeExtension_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [EnumTypeExtension_Sequence2] -> String -> String
$cshowList :: [EnumTypeExtension_Sequence2] -> String -> String
show :: EnumTypeExtension_Sequence2 -> String
$cshow :: EnumTypeExtension_Sequence2 -> String
showsPrec :: Int -> EnumTypeExtension_Sequence2 -> String -> String
$cshowsPrec :: Int -> EnumTypeExtension_Sequence2 -> String -> String
Show)

_EnumTypeExtension_Sequence2 :: Name
_EnumTypeExtension_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.EnumTypeExtension.Sequence2")

_EnumTypeExtension_Sequence2_name :: FieldName
_EnumTypeExtension_Sequence2_name = (String -> FieldName
Core.FieldName String
"name")

_EnumTypeExtension_Sequence2_directives :: FieldName
_EnumTypeExtension_Sequence2_directives = (String -> FieldName
Core.FieldName String
"directives")

data InputObjectTypeDefinition = 
  InputObjectTypeDefinitionSequence InputObjectTypeDefinition_Sequence |
  InputObjectTypeDefinitionSequence2 InputObjectTypeDefinition_Sequence2
  deriving (InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
$c/= :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
== :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
$c== :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
Eq, Eq InputObjectTypeDefinition
InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
InputObjectTypeDefinition -> InputObjectTypeDefinition -> Ordering
InputObjectTypeDefinition
-> InputObjectTypeDefinition -> InputObjectTypeDefinition
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
min :: InputObjectTypeDefinition
-> InputObjectTypeDefinition -> InputObjectTypeDefinition
$cmin :: InputObjectTypeDefinition
-> InputObjectTypeDefinition -> InputObjectTypeDefinition
max :: InputObjectTypeDefinition
-> InputObjectTypeDefinition -> InputObjectTypeDefinition
$cmax :: InputObjectTypeDefinition
-> InputObjectTypeDefinition -> InputObjectTypeDefinition
>= :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
$c>= :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
> :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
$c> :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
<= :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
$c<= :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
< :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
$c< :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
compare :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Ordering
$ccompare :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Ordering
Ord, ReadPrec [InputObjectTypeDefinition]
ReadPrec InputObjectTypeDefinition
Int -> ReadS InputObjectTypeDefinition
ReadS [InputObjectTypeDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InputObjectTypeDefinition]
$creadListPrec :: ReadPrec [InputObjectTypeDefinition]
readPrec :: ReadPrec InputObjectTypeDefinition
$creadPrec :: ReadPrec InputObjectTypeDefinition
readList :: ReadS [InputObjectTypeDefinition]
$creadList :: ReadS [InputObjectTypeDefinition]
readsPrec :: Int -> ReadS InputObjectTypeDefinition
$creadsPrec :: Int -> ReadS InputObjectTypeDefinition
Read, Int -> InputObjectTypeDefinition -> String -> String
[InputObjectTypeDefinition] -> String -> String
InputObjectTypeDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InputObjectTypeDefinition] -> String -> String
$cshowList :: [InputObjectTypeDefinition] -> String -> String
show :: InputObjectTypeDefinition -> String
$cshow :: InputObjectTypeDefinition -> String
showsPrec :: Int -> InputObjectTypeDefinition -> String -> String
$cshowsPrec :: Int -> InputObjectTypeDefinition -> String -> String
Show)

_InputObjectTypeDefinition :: Name
_InputObjectTypeDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InputObjectTypeDefinition")

_InputObjectTypeDefinition_sequence :: FieldName
_InputObjectTypeDefinition_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_InputObjectTypeDefinition_sequence2 :: FieldName
_InputObjectTypeDefinition_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data InputObjectTypeDefinition_Sequence = 
  InputObjectTypeDefinition_Sequence {
    InputObjectTypeDefinition_Sequence -> Maybe Description
inputObjectTypeDefinition_SequenceDescription :: (Maybe Description),
    InputObjectTypeDefinition_Sequence -> Name
inputObjectTypeDefinition_SequenceName :: Name,
    InputObjectTypeDefinition_Sequence -> Maybe Directives
inputObjectTypeDefinition_SequenceDirectives :: (Maybe Directives),
    InputObjectTypeDefinition_Sequence -> InputFieldsDefinition
inputObjectTypeDefinition_SequenceInputFieldsDefinition :: InputFieldsDefinition}
  deriving (InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
$c/= :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
== :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
$c== :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
Eq, Eq InputObjectTypeDefinition_Sequence
InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Ordering
InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
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
min :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
$cmin :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
max :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
$cmax :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
>= :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
$c>= :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
> :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
$c> :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
<= :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
$c<= :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
< :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
$c< :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
compare :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Ordering
$ccompare :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Ordering
Ord, ReadPrec [InputObjectTypeDefinition_Sequence]
ReadPrec InputObjectTypeDefinition_Sequence
Int -> ReadS InputObjectTypeDefinition_Sequence
ReadS [InputObjectTypeDefinition_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InputObjectTypeDefinition_Sequence]
$creadListPrec :: ReadPrec [InputObjectTypeDefinition_Sequence]
readPrec :: ReadPrec InputObjectTypeDefinition_Sequence
$creadPrec :: ReadPrec InputObjectTypeDefinition_Sequence
readList :: ReadS [InputObjectTypeDefinition_Sequence]
$creadList :: ReadS [InputObjectTypeDefinition_Sequence]
readsPrec :: Int -> ReadS InputObjectTypeDefinition_Sequence
$creadsPrec :: Int -> ReadS InputObjectTypeDefinition_Sequence
Read, Int -> InputObjectTypeDefinition_Sequence -> String -> String
[InputObjectTypeDefinition_Sequence] -> String -> String
InputObjectTypeDefinition_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InputObjectTypeDefinition_Sequence] -> String -> String
$cshowList :: [InputObjectTypeDefinition_Sequence] -> String -> String
show :: InputObjectTypeDefinition_Sequence -> String
$cshow :: InputObjectTypeDefinition_Sequence -> String
showsPrec :: Int -> InputObjectTypeDefinition_Sequence -> String -> String
$cshowsPrec :: Int -> InputObjectTypeDefinition_Sequence -> String -> String
Show)

_InputObjectTypeDefinition_Sequence :: Name
_InputObjectTypeDefinition_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InputObjectTypeDefinition.Sequence")

_InputObjectTypeDefinition_Sequence_description :: FieldName
_InputObjectTypeDefinition_Sequence_description = (String -> FieldName
Core.FieldName String
"description")

_InputObjectTypeDefinition_Sequence_name :: FieldName
_InputObjectTypeDefinition_Sequence_name = (String -> FieldName
Core.FieldName String
"name")

_InputObjectTypeDefinition_Sequence_directives :: FieldName
_InputObjectTypeDefinition_Sequence_directives = (String -> FieldName
Core.FieldName String
"directives")

_InputObjectTypeDefinition_Sequence_inputFieldsDefinition :: FieldName
_InputObjectTypeDefinition_Sequence_inputFieldsDefinition = (String -> FieldName
Core.FieldName String
"inputFieldsDefinition")

data InputObjectTypeDefinition_Sequence2 = 
  InputObjectTypeDefinition_Sequence2 {
    InputObjectTypeDefinition_Sequence2 -> Maybe Description
inputObjectTypeDefinition_Sequence2Description :: (Maybe Description),
    InputObjectTypeDefinition_Sequence2 -> Name
inputObjectTypeDefinition_Sequence2Name :: Name,
    InputObjectTypeDefinition_Sequence2 -> Maybe Directives
inputObjectTypeDefinition_Sequence2Directives :: (Maybe Directives)}
  deriving (InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
$c/= :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
== :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
$c== :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
Eq, Eq InputObjectTypeDefinition_Sequence2
InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Ordering
InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
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
min :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
$cmin :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
max :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
$cmax :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
>= :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
$c>= :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
> :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
$c> :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
<= :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
$c<= :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
< :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
$c< :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
compare :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Ordering
$ccompare :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Ordering
Ord, ReadPrec [InputObjectTypeDefinition_Sequence2]
ReadPrec InputObjectTypeDefinition_Sequence2
Int -> ReadS InputObjectTypeDefinition_Sequence2
ReadS [InputObjectTypeDefinition_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InputObjectTypeDefinition_Sequence2]
$creadListPrec :: ReadPrec [InputObjectTypeDefinition_Sequence2]
readPrec :: ReadPrec InputObjectTypeDefinition_Sequence2
$creadPrec :: ReadPrec InputObjectTypeDefinition_Sequence2
readList :: ReadS [InputObjectTypeDefinition_Sequence2]
$creadList :: ReadS [InputObjectTypeDefinition_Sequence2]
readsPrec :: Int -> ReadS InputObjectTypeDefinition_Sequence2
$creadsPrec :: Int -> ReadS InputObjectTypeDefinition_Sequence2
Read, Int -> InputObjectTypeDefinition_Sequence2 -> String -> String
[InputObjectTypeDefinition_Sequence2] -> String -> String
InputObjectTypeDefinition_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InputObjectTypeDefinition_Sequence2] -> String -> String
$cshowList :: [InputObjectTypeDefinition_Sequence2] -> String -> String
show :: InputObjectTypeDefinition_Sequence2 -> String
$cshow :: InputObjectTypeDefinition_Sequence2 -> String
showsPrec :: Int -> InputObjectTypeDefinition_Sequence2 -> String -> String
$cshowsPrec :: Int -> InputObjectTypeDefinition_Sequence2 -> String -> String
Show)

_InputObjectTypeDefinition_Sequence2 :: Name
_InputObjectTypeDefinition_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InputObjectTypeDefinition.Sequence2")

_InputObjectTypeDefinition_Sequence2_description :: FieldName
_InputObjectTypeDefinition_Sequence2_description = (String -> FieldName
Core.FieldName String
"description")

_InputObjectTypeDefinition_Sequence2_name :: FieldName
_InputObjectTypeDefinition_Sequence2_name = (String -> FieldName
Core.FieldName String
"name")

_InputObjectTypeDefinition_Sequence2_directives :: FieldName
_InputObjectTypeDefinition_Sequence2_directives = (String -> FieldName
Core.FieldName String
"directives")

data InputFieldsDefinition = 
  InputFieldsDefinition {
    InputFieldsDefinition -> [InputValueDefinition]
inputFieldsDefinitionListOfInputValueDefinition :: [InputValueDefinition]}
  deriving (InputFieldsDefinition -> InputFieldsDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
$c/= :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
== :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
$c== :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
Eq, Eq InputFieldsDefinition
InputFieldsDefinition -> InputFieldsDefinition -> Bool
InputFieldsDefinition -> InputFieldsDefinition -> Ordering
InputFieldsDefinition
-> InputFieldsDefinition -> InputFieldsDefinition
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
min :: InputFieldsDefinition
-> InputFieldsDefinition -> InputFieldsDefinition
$cmin :: InputFieldsDefinition
-> InputFieldsDefinition -> InputFieldsDefinition
max :: InputFieldsDefinition
-> InputFieldsDefinition -> InputFieldsDefinition
$cmax :: InputFieldsDefinition
-> InputFieldsDefinition -> InputFieldsDefinition
>= :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
$c>= :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
> :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
$c> :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
<= :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
$c<= :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
< :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
$c< :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
compare :: InputFieldsDefinition -> InputFieldsDefinition -> Ordering
$ccompare :: InputFieldsDefinition -> InputFieldsDefinition -> Ordering
Ord, ReadPrec [InputFieldsDefinition]
ReadPrec InputFieldsDefinition
Int -> ReadS InputFieldsDefinition
ReadS [InputFieldsDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InputFieldsDefinition]
$creadListPrec :: ReadPrec [InputFieldsDefinition]
readPrec :: ReadPrec InputFieldsDefinition
$creadPrec :: ReadPrec InputFieldsDefinition
readList :: ReadS [InputFieldsDefinition]
$creadList :: ReadS [InputFieldsDefinition]
readsPrec :: Int -> ReadS InputFieldsDefinition
$creadsPrec :: Int -> ReadS InputFieldsDefinition
Read, Int -> InputFieldsDefinition -> String -> String
[InputFieldsDefinition] -> String -> String
InputFieldsDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InputFieldsDefinition] -> String -> String
$cshowList :: [InputFieldsDefinition] -> String -> String
show :: InputFieldsDefinition -> String
$cshow :: InputFieldsDefinition -> String
showsPrec :: Int -> InputFieldsDefinition -> String -> String
$cshowsPrec :: Int -> InputFieldsDefinition -> String -> String
Show)

_InputFieldsDefinition :: Name
_InputFieldsDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InputFieldsDefinition")

_InputFieldsDefinition_listOfInputValueDefinition :: FieldName
_InputFieldsDefinition_listOfInputValueDefinition = (String -> FieldName
Core.FieldName String
"listOfInputValueDefinition")

data InputObjectTypeExtension = 
  InputObjectTypeExtensionSequence InputObjectTypeExtension_Sequence |
  InputObjectTypeExtensionSequence2 InputObjectTypeExtension_Sequence2
  deriving (InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
$c/= :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
== :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
$c== :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
Eq, Eq InputObjectTypeExtension
InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
InputObjectTypeExtension -> InputObjectTypeExtension -> Ordering
InputObjectTypeExtension
-> InputObjectTypeExtension -> InputObjectTypeExtension
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
min :: InputObjectTypeExtension
-> InputObjectTypeExtension -> InputObjectTypeExtension
$cmin :: InputObjectTypeExtension
-> InputObjectTypeExtension -> InputObjectTypeExtension
max :: InputObjectTypeExtension
-> InputObjectTypeExtension -> InputObjectTypeExtension
$cmax :: InputObjectTypeExtension
-> InputObjectTypeExtension -> InputObjectTypeExtension
>= :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
$c>= :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
> :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
$c> :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
<= :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
$c<= :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
< :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
$c< :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
compare :: InputObjectTypeExtension -> InputObjectTypeExtension -> Ordering
$ccompare :: InputObjectTypeExtension -> InputObjectTypeExtension -> Ordering
Ord, ReadPrec [InputObjectTypeExtension]
ReadPrec InputObjectTypeExtension
Int -> ReadS InputObjectTypeExtension
ReadS [InputObjectTypeExtension]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InputObjectTypeExtension]
$creadListPrec :: ReadPrec [InputObjectTypeExtension]
readPrec :: ReadPrec InputObjectTypeExtension
$creadPrec :: ReadPrec InputObjectTypeExtension
readList :: ReadS [InputObjectTypeExtension]
$creadList :: ReadS [InputObjectTypeExtension]
readsPrec :: Int -> ReadS InputObjectTypeExtension
$creadsPrec :: Int -> ReadS InputObjectTypeExtension
Read, Int -> InputObjectTypeExtension -> String -> String
[InputObjectTypeExtension] -> String -> String
InputObjectTypeExtension -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InputObjectTypeExtension] -> String -> String
$cshowList :: [InputObjectTypeExtension] -> String -> String
show :: InputObjectTypeExtension -> String
$cshow :: InputObjectTypeExtension -> String
showsPrec :: Int -> InputObjectTypeExtension -> String -> String
$cshowsPrec :: Int -> InputObjectTypeExtension -> String -> String
Show)

_InputObjectTypeExtension :: Name
_InputObjectTypeExtension = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InputObjectTypeExtension")

_InputObjectTypeExtension_sequence :: FieldName
_InputObjectTypeExtension_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_InputObjectTypeExtension_sequence2 :: FieldName
_InputObjectTypeExtension_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data InputObjectTypeExtension_Sequence = 
  InputObjectTypeExtension_Sequence {
    InputObjectTypeExtension_Sequence -> Name
inputObjectTypeExtension_SequenceName :: Name,
    InputObjectTypeExtension_Sequence -> Maybe Directives
inputObjectTypeExtension_SequenceDirectives :: (Maybe Directives),
    InputObjectTypeExtension_Sequence -> InputFieldsDefinition
inputObjectTypeExtension_SequenceInputFieldsDefinition :: InputFieldsDefinition}
  deriving (InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
$c/= :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
== :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
$c== :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
Eq, Eq InputObjectTypeExtension_Sequence
InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Ordering
InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
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
min :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
$cmin :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
max :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
$cmax :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
>= :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
$c>= :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
> :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
$c> :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
<= :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
$c<= :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
< :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
$c< :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
compare :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Ordering
$ccompare :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Ordering
Ord, ReadPrec [InputObjectTypeExtension_Sequence]
ReadPrec InputObjectTypeExtension_Sequence
Int -> ReadS InputObjectTypeExtension_Sequence
ReadS [InputObjectTypeExtension_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InputObjectTypeExtension_Sequence]
$creadListPrec :: ReadPrec [InputObjectTypeExtension_Sequence]
readPrec :: ReadPrec InputObjectTypeExtension_Sequence
$creadPrec :: ReadPrec InputObjectTypeExtension_Sequence
readList :: ReadS [InputObjectTypeExtension_Sequence]
$creadList :: ReadS [InputObjectTypeExtension_Sequence]
readsPrec :: Int -> ReadS InputObjectTypeExtension_Sequence
$creadsPrec :: Int -> ReadS InputObjectTypeExtension_Sequence
Read, Int -> InputObjectTypeExtension_Sequence -> String -> String
[InputObjectTypeExtension_Sequence] -> String -> String
InputObjectTypeExtension_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InputObjectTypeExtension_Sequence] -> String -> String
$cshowList :: [InputObjectTypeExtension_Sequence] -> String -> String
show :: InputObjectTypeExtension_Sequence -> String
$cshow :: InputObjectTypeExtension_Sequence -> String
showsPrec :: Int -> InputObjectTypeExtension_Sequence -> String -> String
$cshowsPrec :: Int -> InputObjectTypeExtension_Sequence -> String -> String
Show)

_InputObjectTypeExtension_Sequence :: Name
_InputObjectTypeExtension_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InputObjectTypeExtension.Sequence")

_InputObjectTypeExtension_Sequence_name :: FieldName
_InputObjectTypeExtension_Sequence_name = (String -> FieldName
Core.FieldName String
"name")

_InputObjectTypeExtension_Sequence_directives :: FieldName
_InputObjectTypeExtension_Sequence_directives = (String -> FieldName
Core.FieldName String
"directives")

_InputObjectTypeExtension_Sequence_inputFieldsDefinition :: FieldName
_InputObjectTypeExtension_Sequence_inputFieldsDefinition = (String -> FieldName
Core.FieldName String
"inputFieldsDefinition")

data InputObjectTypeExtension_Sequence2 = 
  InputObjectTypeExtension_Sequence2 {
    InputObjectTypeExtension_Sequence2 -> Name
inputObjectTypeExtension_Sequence2Name :: Name,
    InputObjectTypeExtension_Sequence2 -> Directives
inputObjectTypeExtension_Sequence2Directives :: Directives}
  deriving (InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
$c/= :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
== :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
$c== :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
Eq, Eq InputObjectTypeExtension_Sequence2
InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Ordering
InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
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
min :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
$cmin :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
max :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
$cmax :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
>= :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
$c>= :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
> :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
$c> :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
<= :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
$c<= :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
< :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
$c< :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
compare :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Ordering
$ccompare :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Ordering
Ord, ReadPrec [InputObjectTypeExtension_Sequence2]
ReadPrec InputObjectTypeExtension_Sequence2
Int -> ReadS InputObjectTypeExtension_Sequence2
ReadS [InputObjectTypeExtension_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [InputObjectTypeExtension_Sequence2]
$creadListPrec :: ReadPrec [InputObjectTypeExtension_Sequence2]
readPrec :: ReadPrec InputObjectTypeExtension_Sequence2
$creadPrec :: ReadPrec InputObjectTypeExtension_Sequence2
readList :: ReadS [InputObjectTypeExtension_Sequence2]
$creadList :: ReadS [InputObjectTypeExtension_Sequence2]
readsPrec :: Int -> ReadS InputObjectTypeExtension_Sequence2
$creadsPrec :: Int -> ReadS InputObjectTypeExtension_Sequence2
Read, Int -> InputObjectTypeExtension_Sequence2 -> String -> String
[InputObjectTypeExtension_Sequence2] -> String -> String
InputObjectTypeExtension_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [InputObjectTypeExtension_Sequence2] -> String -> String
$cshowList :: [InputObjectTypeExtension_Sequence2] -> String -> String
show :: InputObjectTypeExtension_Sequence2 -> String
$cshow :: InputObjectTypeExtension_Sequence2 -> String
showsPrec :: Int -> InputObjectTypeExtension_Sequence2 -> String -> String
$cshowsPrec :: Int -> InputObjectTypeExtension_Sequence2 -> String -> String
Show)

_InputObjectTypeExtension_Sequence2 :: Name
_InputObjectTypeExtension_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.InputObjectTypeExtension.Sequence2")

_InputObjectTypeExtension_Sequence2_name :: FieldName
_InputObjectTypeExtension_Sequence2_name = (String -> FieldName
Core.FieldName String
"name")

_InputObjectTypeExtension_Sequence2_directives :: FieldName
_InputObjectTypeExtension_Sequence2_directives = (String -> FieldName
Core.FieldName String
"directives")

data DirectiveDefinition = 
  DirectiveDefinition {
    DirectiveDefinition -> Maybe Description
directiveDefinitionDescription :: (Maybe Description),
    DirectiveDefinition -> Name
directiveDefinitionName :: Name,
    DirectiveDefinition -> Maybe ArgumentsDefinition
directiveDefinitionArgumentsDefinition :: (Maybe ArgumentsDefinition),
    DirectiveDefinition -> Maybe ()
directiveDefinitionRepeatable :: (Maybe ()),
    DirectiveDefinition -> DirectiveLocations
directiveDefinitionDirectiveLocations :: DirectiveLocations}
  deriving (DirectiveDefinition -> DirectiveDefinition -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DirectiveDefinition -> DirectiveDefinition -> Bool
$c/= :: DirectiveDefinition -> DirectiveDefinition -> Bool
== :: DirectiveDefinition -> DirectiveDefinition -> Bool
$c== :: DirectiveDefinition -> DirectiveDefinition -> Bool
Eq, Eq DirectiveDefinition
DirectiveDefinition -> DirectiveDefinition -> Bool
DirectiveDefinition -> DirectiveDefinition -> Ordering
DirectiveDefinition -> DirectiveDefinition -> DirectiveDefinition
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
min :: DirectiveDefinition -> DirectiveDefinition -> DirectiveDefinition
$cmin :: DirectiveDefinition -> DirectiveDefinition -> DirectiveDefinition
max :: DirectiveDefinition -> DirectiveDefinition -> DirectiveDefinition
$cmax :: DirectiveDefinition -> DirectiveDefinition -> DirectiveDefinition
>= :: DirectiveDefinition -> DirectiveDefinition -> Bool
$c>= :: DirectiveDefinition -> DirectiveDefinition -> Bool
> :: DirectiveDefinition -> DirectiveDefinition -> Bool
$c> :: DirectiveDefinition -> DirectiveDefinition -> Bool
<= :: DirectiveDefinition -> DirectiveDefinition -> Bool
$c<= :: DirectiveDefinition -> DirectiveDefinition -> Bool
< :: DirectiveDefinition -> DirectiveDefinition -> Bool
$c< :: DirectiveDefinition -> DirectiveDefinition -> Bool
compare :: DirectiveDefinition -> DirectiveDefinition -> Ordering
$ccompare :: DirectiveDefinition -> DirectiveDefinition -> Ordering
Ord, ReadPrec [DirectiveDefinition]
ReadPrec DirectiveDefinition
Int -> ReadS DirectiveDefinition
ReadS [DirectiveDefinition]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DirectiveDefinition]
$creadListPrec :: ReadPrec [DirectiveDefinition]
readPrec :: ReadPrec DirectiveDefinition
$creadPrec :: ReadPrec DirectiveDefinition
readList :: ReadS [DirectiveDefinition]
$creadList :: ReadS [DirectiveDefinition]
readsPrec :: Int -> ReadS DirectiveDefinition
$creadsPrec :: Int -> ReadS DirectiveDefinition
Read, Int -> DirectiveDefinition -> String -> String
[DirectiveDefinition] -> String -> String
DirectiveDefinition -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DirectiveDefinition] -> String -> String
$cshowList :: [DirectiveDefinition] -> String -> String
show :: DirectiveDefinition -> String
$cshow :: DirectiveDefinition -> String
showsPrec :: Int -> DirectiveDefinition -> String -> String
$cshowsPrec :: Int -> DirectiveDefinition -> String -> String
Show)

_DirectiveDefinition :: Name
_DirectiveDefinition = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.DirectiveDefinition")

_DirectiveDefinition_description :: FieldName
_DirectiveDefinition_description = (String -> FieldName
Core.FieldName String
"description")

_DirectiveDefinition_name :: FieldName
_DirectiveDefinition_name = (String -> FieldName
Core.FieldName String
"name")

_DirectiveDefinition_argumentsDefinition :: FieldName
_DirectiveDefinition_argumentsDefinition = (String -> FieldName
Core.FieldName String
"argumentsDefinition")

_DirectiveDefinition_repeatable :: FieldName
_DirectiveDefinition_repeatable = (String -> FieldName
Core.FieldName String
"repeatable")

_DirectiveDefinition_directiveLocations :: FieldName
_DirectiveDefinition_directiveLocations = (String -> FieldName
Core.FieldName String
"directiveLocations")

data DirectiveLocations = 
  DirectiveLocationsSequence DirectiveLocations_Sequence |
  DirectiveLocationsSequence2 DirectiveLocations_Sequence2
  deriving (DirectiveLocations -> DirectiveLocations -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DirectiveLocations -> DirectiveLocations -> Bool
$c/= :: DirectiveLocations -> DirectiveLocations -> Bool
== :: DirectiveLocations -> DirectiveLocations -> Bool
$c== :: DirectiveLocations -> DirectiveLocations -> Bool
Eq, Eq DirectiveLocations
DirectiveLocations -> DirectiveLocations -> Bool
DirectiveLocations -> DirectiveLocations -> Ordering
DirectiveLocations -> DirectiveLocations -> DirectiveLocations
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
min :: DirectiveLocations -> DirectiveLocations -> DirectiveLocations
$cmin :: DirectiveLocations -> DirectiveLocations -> DirectiveLocations
max :: DirectiveLocations -> DirectiveLocations -> DirectiveLocations
$cmax :: DirectiveLocations -> DirectiveLocations -> DirectiveLocations
>= :: DirectiveLocations -> DirectiveLocations -> Bool
$c>= :: DirectiveLocations -> DirectiveLocations -> Bool
> :: DirectiveLocations -> DirectiveLocations -> Bool
$c> :: DirectiveLocations -> DirectiveLocations -> Bool
<= :: DirectiveLocations -> DirectiveLocations -> Bool
$c<= :: DirectiveLocations -> DirectiveLocations -> Bool
< :: DirectiveLocations -> DirectiveLocations -> Bool
$c< :: DirectiveLocations -> DirectiveLocations -> Bool
compare :: DirectiveLocations -> DirectiveLocations -> Ordering
$ccompare :: DirectiveLocations -> DirectiveLocations -> Ordering
Ord, ReadPrec [DirectiveLocations]
ReadPrec DirectiveLocations
Int -> ReadS DirectiveLocations
ReadS [DirectiveLocations]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DirectiveLocations]
$creadListPrec :: ReadPrec [DirectiveLocations]
readPrec :: ReadPrec DirectiveLocations
$creadPrec :: ReadPrec DirectiveLocations
readList :: ReadS [DirectiveLocations]
$creadList :: ReadS [DirectiveLocations]
readsPrec :: Int -> ReadS DirectiveLocations
$creadsPrec :: Int -> ReadS DirectiveLocations
Read, Int -> DirectiveLocations -> String -> String
[DirectiveLocations] -> String -> String
DirectiveLocations -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DirectiveLocations] -> String -> String
$cshowList :: [DirectiveLocations] -> String -> String
show :: DirectiveLocations -> String
$cshow :: DirectiveLocations -> String
showsPrec :: Int -> DirectiveLocations -> String -> String
$cshowsPrec :: Int -> DirectiveLocations -> String -> String
Show)

_DirectiveLocations :: Name
_DirectiveLocations = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.DirectiveLocations")

_DirectiveLocations_sequence :: FieldName
_DirectiveLocations_sequence = (String -> FieldName
Core.FieldName String
"sequence")

_DirectiveLocations_sequence2 :: FieldName
_DirectiveLocations_sequence2 = (String -> FieldName
Core.FieldName String
"sequence2")

data DirectiveLocations_Sequence = 
  DirectiveLocations_Sequence {
    DirectiveLocations_Sequence -> DirectiveLocations
directiveLocations_SequenceDirectiveLocations :: DirectiveLocations,
    DirectiveLocations_Sequence -> DirectiveLocation
directiveLocations_SequenceDirectiveLocation :: DirectiveLocation}
  deriving (DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
$c/= :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
== :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
$c== :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
Eq, Eq DirectiveLocations_Sequence
DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> Ordering
DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> DirectiveLocations_Sequence
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
min :: DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> DirectiveLocations_Sequence
$cmin :: DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> DirectiveLocations_Sequence
max :: DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> DirectiveLocations_Sequence
$cmax :: DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> DirectiveLocations_Sequence
>= :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
$c>= :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
> :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
$c> :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
<= :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
$c<= :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
< :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
$c< :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
compare :: DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> Ordering
$ccompare :: DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> Ordering
Ord, ReadPrec [DirectiveLocations_Sequence]
ReadPrec DirectiveLocations_Sequence
Int -> ReadS DirectiveLocations_Sequence
ReadS [DirectiveLocations_Sequence]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DirectiveLocations_Sequence]
$creadListPrec :: ReadPrec [DirectiveLocations_Sequence]
readPrec :: ReadPrec DirectiveLocations_Sequence
$creadPrec :: ReadPrec DirectiveLocations_Sequence
readList :: ReadS [DirectiveLocations_Sequence]
$creadList :: ReadS [DirectiveLocations_Sequence]
readsPrec :: Int -> ReadS DirectiveLocations_Sequence
$creadsPrec :: Int -> ReadS DirectiveLocations_Sequence
Read, Int -> DirectiveLocations_Sequence -> String -> String
[DirectiveLocations_Sequence] -> String -> String
DirectiveLocations_Sequence -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DirectiveLocations_Sequence] -> String -> String
$cshowList :: [DirectiveLocations_Sequence] -> String -> String
show :: DirectiveLocations_Sequence -> String
$cshow :: DirectiveLocations_Sequence -> String
showsPrec :: Int -> DirectiveLocations_Sequence -> String -> String
$cshowsPrec :: Int -> DirectiveLocations_Sequence -> String -> String
Show)

_DirectiveLocations_Sequence :: Name
_DirectiveLocations_Sequence = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.DirectiveLocations.Sequence")

_DirectiveLocations_Sequence_directiveLocations :: FieldName
_DirectiveLocations_Sequence_directiveLocations = (String -> FieldName
Core.FieldName String
"directiveLocations")

_DirectiveLocations_Sequence_directiveLocation :: FieldName
_DirectiveLocations_Sequence_directiveLocation = (String -> FieldName
Core.FieldName String
"directiveLocation")

data DirectiveLocations_Sequence2 = 
  DirectiveLocations_Sequence2 {
    DirectiveLocations_Sequence2 -> Maybe ()
directiveLocations_Sequence2Or :: (Maybe ()),
    DirectiveLocations_Sequence2 -> DirectiveLocation
directiveLocations_Sequence2DirectiveLocation :: DirectiveLocation}
  deriving (DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
$c/= :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
== :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
$c== :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
Eq, Eq DirectiveLocations_Sequence2
DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Ordering
DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> DirectiveLocations_Sequence2
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
min :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> DirectiveLocations_Sequence2
$cmin :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> DirectiveLocations_Sequence2
max :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> DirectiveLocations_Sequence2
$cmax :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> DirectiveLocations_Sequence2
>= :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
$c>= :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
> :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
$c> :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
<= :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
$c<= :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
< :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
$c< :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
compare :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Ordering
$ccompare :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Ordering
Ord, ReadPrec [DirectiveLocations_Sequence2]
ReadPrec DirectiveLocations_Sequence2
Int -> ReadS DirectiveLocations_Sequence2
ReadS [DirectiveLocations_Sequence2]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DirectiveLocations_Sequence2]
$creadListPrec :: ReadPrec [DirectiveLocations_Sequence2]
readPrec :: ReadPrec DirectiveLocations_Sequence2
$creadPrec :: ReadPrec DirectiveLocations_Sequence2
readList :: ReadS [DirectiveLocations_Sequence2]
$creadList :: ReadS [DirectiveLocations_Sequence2]
readsPrec :: Int -> ReadS DirectiveLocations_Sequence2
$creadsPrec :: Int -> ReadS DirectiveLocations_Sequence2
Read, Int -> DirectiveLocations_Sequence2 -> String -> String
[DirectiveLocations_Sequence2] -> String -> String
DirectiveLocations_Sequence2 -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DirectiveLocations_Sequence2] -> String -> String
$cshowList :: [DirectiveLocations_Sequence2] -> String -> String
show :: DirectiveLocations_Sequence2 -> String
$cshow :: DirectiveLocations_Sequence2 -> String
showsPrec :: Int -> DirectiveLocations_Sequence2 -> String -> String
$cshowsPrec :: Int -> DirectiveLocations_Sequence2 -> String -> String
Show)

_DirectiveLocations_Sequence2 :: Name
_DirectiveLocations_Sequence2 = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.DirectiveLocations.Sequence2")

_DirectiveLocations_Sequence2_or :: FieldName
_DirectiveLocations_Sequence2_or = (String -> FieldName
Core.FieldName String
"or")

_DirectiveLocations_Sequence2_directiveLocation :: FieldName
_DirectiveLocations_Sequence2_directiveLocation = (String -> FieldName
Core.FieldName String
"directiveLocation")

data DirectiveLocation = 
  DirectiveLocationExecutable ExecutableDirectiveLocation |
  DirectiveLocationTypeSystem TypeSystemDirectiveLocation
  deriving (DirectiveLocation -> DirectiveLocation -> Bool
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, Eq DirectiveLocation
DirectiveLocation -> DirectiveLocation -> Bool
DirectiveLocation -> DirectiveLocation -> Ordering
DirectiveLocation -> DirectiveLocation -> DirectiveLocation
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
min :: DirectiveLocation -> DirectiveLocation -> DirectiveLocation
$cmin :: DirectiveLocation -> DirectiveLocation -> DirectiveLocation
max :: DirectiveLocation -> DirectiveLocation -> DirectiveLocation
$cmax :: DirectiveLocation -> DirectiveLocation -> DirectiveLocation
>= :: DirectiveLocation -> DirectiveLocation -> Bool
$c>= :: DirectiveLocation -> DirectiveLocation -> Bool
> :: DirectiveLocation -> DirectiveLocation -> Bool
$c> :: DirectiveLocation -> DirectiveLocation -> Bool
<= :: DirectiveLocation -> DirectiveLocation -> Bool
$c<= :: DirectiveLocation -> DirectiveLocation -> Bool
< :: DirectiveLocation -> DirectiveLocation -> Bool
$c< :: DirectiveLocation -> DirectiveLocation -> Bool
compare :: DirectiveLocation -> DirectiveLocation -> Ordering
$ccompare :: DirectiveLocation -> DirectiveLocation -> Ordering
Ord, ReadPrec [DirectiveLocation]
ReadPrec DirectiveLocation
Int -> ReadS DirectiveLocation
ReadS [DirectiveLocation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [DirectiveLocation]
$creadListPrec :: ReadPrec [DirectiveLocation]
readPrec :: ReadPrec DirectiveLocation
$creadPrec :: ReadPrec DirectiveLocation
readList :: ReadS [DirectiveLocation]
$creadList :: ReadS [DirectiveLocation]
readsPrec :: Int -> ReadS DirectiveLocation
$creadsPrec :: Int -> ReadS DirectiveLocation
Read, Int -> DirectiveLocation -> String -> String
[DirectiveLocation] -> String -> String
DirectiveLocation -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [DirectiveLocation] -> String -> String
$cshowList :: [DirectiveLocation] -> String -> String
show :: DirectiveLocation -> String
$cshow :: DirectiveLocation -> String
showsPrec :: Int -> DirectiveLocation -> String -> String
$cshowsPrec :: Int -> DirectiveLocation -> String -> String
Show)

_DirectiveLocation :: Name
_DirectiveLocation = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.DirectiveLocation")

_DirectiveLocation_executable :: FieldName
_DirectiveLocation_executable = (String -> FieldName
Core.FieldName String
"executable")

_DirectiveLocation_typeSystem :: FieldName
_DirectiveLocation_typeSystem = (String -> FieldName
Core.FieldName String
"typeSystem")

data ExecutableDirectiveLocation = 
  ExecutableDirectiveLocationQUERY  |
  ExecutableDirectiveLocationMUTATION  |
  ExecutableDirectiveLocationSUBSCRIPTION  |
  ExecutableDirectiveLocationFIELD  |
  ExecutableDirectiveLocationFRAGMENTLowbarDEFINITION  |
  ExecutableDirectiveLocationFRAGMENTLowbarSPREAD  |
  ExecutableDirectiveLocationINLINELowbarFRAGMENT  |
  ExecutableDirectiveLocationVARIABLELowbarDEFINITION 
  deriving (ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
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, Eq ExecutableDirectiveLocation
ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Ordering
ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> ExecutableDirectiveLocation
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
min :: ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> ExecutableDirectiveLocation
$cmin :: ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> ExecutableDirectiveLocation
max :: ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> ExecutableDirectiveLocation
$cmax :: ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> ExecutableDirectiveLocation
>= :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
$c>= :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
> :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
$c> :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
<= :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
$c<= :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
< :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
$c< :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
compare :: ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Ordering
$ccompare :: ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Ordering
Ord, ReadPrec [ExecutableDirectiveLocation]
ReadPrec ExecutableDirectiveLocation
Int -> ReadS ExecutableDirectiveLocation
ReadS [ExecutableDirectiveLocation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [ExecutableDirectiveLocation]
$creadListPrec :: ReadPrec [ExecutableDirectiveLocation]
readPrec :: ReadPrec ExecutableDirectiveLocation
$creadPrec :: ReadPrec ExecutableDirectiveLocation
readList :: ReadS [ExecutableDirectiveLocation]
$creadList :: ReadS [ExecutableDirectiveLocation]
readsPrec :: Int -> ReadS ExecutableDirectiveLocation
$creadsPrec :: Int -> ReadS ExecutableDirectiveLocation
Read, Int -> ExecutableDirectiveLocation -> String -> String
[ExecutableDirectiveLocation] -> String -> String
ExecutableDirectiveLocation -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [ExecutableDirectiveLocation] -> String -> String
$cshowList :: [ExecutableDirectiveLocation] -> String -> String
show :: ExecutableDirectiveLocation -> String
$cshow :: ExecutableDirectiveLocation -> String
showsPrec :: Int -> ExecutableDirectiveLocation -> String -> String
$cshowsPrec :: Int -> ExecutableDirectiveLocation -> String -> String
Show)

_ExecutableDirectiveLocation :: Name
_ExecutableDirectiveLocation = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.ExecutableDirectiveLocation")

_ExecutableDirectiveLocation_qUERY :: FieldName
_ExecutableDirectiveLocation_qUERY = (String -> FieldName
Core.FieldName String
"qUERY")

_ExecutableDirectiveLocation_mUTATION :: FieldName
_ExecutableDirectiveLocation_mUTATION = (String -> FieldName
Core.FieldName String
"mUTATION")

_ExecutableDirectiveLocation_sUBSCRIPTION :: FieldName
_ExecutableDirectiveLocation_sUBSCRIPTION = (String -> FieldName
Core.FieldName String
"sUBSCRIPTION")

_ExecutableDirectiveLocation_fIELD :: FieldName
_ExecutableDirectiveLocation_fIELD = (String -> FieldName
Core.FieldName String
"fIELD")

_ExecutableDirectiveLocation_fRAGMENTLowbarDEFINITION :: FieldName
_ExecutableDirectiveLocation_fRAGMENTLowbarDEFINITION = (String -> FieldName
Core.FieldName String
"fRAGMENTLowbarDEFINITION")

_ExecutableDirectiveLocation_fRAGMENTLowbarSPREAD :: FieldName
_ExecutableDirectiveLocation_fRAGMENTLowbarSPREAD = (String -> FieldName
Core.FieldName String
"fRAGMENTLowbarSPREAD")

_ExecutableDirectiveLocation_iNLINELowbarFRAGMENT :: FieldName
_ExecutableDirectiveLocation_iNLINELowbarFRAGMENT = (String -> FieldName
Core.FieldName String
"iNLINELowbarFRAGMENT")

_ExecutableDirectiveLocation_vARIABLELowbarDEFINITION :: FieldName
_ExecutableDirectiveLocation_vARIABLELowbarDEFINITION = (String -> FieldName
Core.FieldName String
"vARIABLELowbarDEFINITION")

data TypeSystemDirectiveLocation = 
  TypeSystemDirectiveLocationSCHEMA  |
  TypeSystemDirectiveLocationSCALAR  |
  TypeSystemDirectiveLocationOBJECT  |
  TypeSystemDirectiveLocationFIELDLowbarDEFINITION  |
  TypeSystemDirectiveLocationARGUMENTLowbarDEFINITION  |
  TypeSystemDirectiveLocationINTERFACE  |
  TypeSystemDirectiveLocationUNION  |
  TypeSystemDirectiveLocationENUM  |
  TypeSystemDirectiveLocationENUMLowbarVALUE  |
  TypeSystemDirectiveLocationINPUTLowbarOBJECT  |
  TypeSystemDirectiveLocationINPUTLowbarFIELDLowbarDEFINITION 
  deriving (TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
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, Eq TypeSystemDirectiveLocation
TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Ordering
TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation
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
min :: TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation
$cmin :: TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation
max :: TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation
$cmax :: TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation
>= :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
$c>= :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
> :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
$c> :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
<= :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
$c<= :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
< :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
$c< :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
compare :: TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Ordering
$ccompare :: TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Ordering
Ord, ReadPrec [TypeSystemDirectiveLocation]
ReadPrec TypeSystemDirectiveLocation
Int -> ReadS TypeSystemDirectiveLocation
ReadS [TypeSystemDirectiveLocation]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [TypeSystemDirectiveLocation]
$creadListPrec :: ReadPrec [TypeSystemDirectiveLocation]
readPrec :: ReadPrec TypeSystemDirectiveLocation
$creadPrec :: ReadPrec TypeSystemDirectiveLocation
readList :: ReadS [TypeSystemDirectiveLocation]
$creadList :: ReadS [TypeSystemDirectiveLocation]
readsPrec :: Int -> ReadS TypeSystemDirectiveLocation
$creadsPrec :: Int -> ReadS TypeSystemDirectiveLocation
Read, Int -> TypeSystemDirectiveLocation -> String -> String
[TypeSystemDirectiveLocation] -> String -> String
TypeSystemDirectiveLocation -> String
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [TypeSystemDirectiveLocation] -> String -> String
$cshowList :: [TypeSystemDirectiveLocation] -> String -> String
show :: TypeSystemDirectiveLocation -> String
$cshow :: TypeSystemDirectiveLocation -> String
showsPrec :: Int -> TypeSystemDirectiveLocation -> String -> String
$cshowsPrec :: Int -> TypeSystemDirectiveLocation -> String -> String
Show)

_TypeSystemDirectiveLocation :: Name
_TypeSystemDirectiveLocation = (String -> Name
Core.Name String
"hydra/ext/graphql/syntax.TypeSystemDirectiveLocation")

_TypeSystemDirectiveLocation_sCHEMA :: FieldName
_TypeSystemDirectiveLocation_sCHEMA = (String -> FieldName
Core.FieldName String
"sCHEMA")

_TypeSystemDirectiveLocation_sCALAR :: FieldName
_TypeSystemDirectiveLocation_sCALAR = (String -> FieldName
Core.FieldName String
"sCALAR")

_TypeSystemDirectiveLocation_oBJECT :: FieldName
_TypeSystemDirectiveLocation_oBJECT = (String -> FieldName
Core.FieldName String
"oBJECT")

_TypeSystemDirectiveLocation_fIELDLowbarDEFINITION :: FieldName
_TypeSystemDirectiveLocation_fIELDLowbarDEFINITION = (String -> FieldName
Core.FieldName String
"fIELDLowbarDEFINITION")

_TypeSystemDirectiveLocation_aRGUMENTLowbarDEFINITION :: FieldName
_TypeSystemDirectiveLocation_aRGUMENTLowbarDEFINITION = (String -> FieldName
Core.FieldName String
"aRGUMENTLowbarDEFINITION")

_TypeSystemDirectiveLocation_iNTERFACE :: FieldName
_TypeSystemDirectiveLocation_iNTERFACE = (String -> FieldName
Core.FieldName String
"iNTERFACE")

_TypeSystemDirectiveLocation_uNION :: FieldName
_TypeSystemDirectiveLocation_uNION = (String -> FieldName
Core.FieldName String
"uNION")

_TypeSystemDirectiveLocation_eNUM :: FieldName
_TypeSystemDirectiveLocation_eNUM = (String -> FieldName
Core.FieldName String
"eNUM")

_TypeSystemDirectiveLocation_eNUMLowbarVALUE :: FieldName
_TypeSystemDirectiveLocation_eNUMLowbarVALUE = (String -> FieldName
Core.FieldName String
"eNUMLowbarVALUE")

_TypeSystemDirectiveLocation_iNPUTLowbarOBJECT :: FieldName
_TypeSystemDirectiveLocation_iNPUTLowbarOBJECT = (String -> FieldName
Core.FieldName String
"iNPUTLowbarOBJECT")

_TypeSystemDirectiveLocation_iNPUTLowbarFIELDLowbarDEFINITION :: FieldName
_TypeSystemDirectiveLocation_iNPUTLowbarFIELDLowbarDEFINITION = (String -> FieldName
Core.FieldName String
"iNPUTLowbarFIELDLowbarDEFINITION")