module Hydra.Langs.Graphql.Syntax where
import qualified Hydra.Core as Core
import Data.Int
import Data.List as L
import Data.Map as M
import Data.Set as S
newtype Name =
Name {
Name -> String
unName :: String}
deriving (Name -> Name -> Bool
(Name -> Name -> Bool) -> (Name -> Name -> Bool) -> Eq Name
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Name -> Name -> Bool
== :: Name -> Name -> Bool
$c/= :: Name -> Name -> Bool
/= :: Name -> Name -> Bool
Eq, Eq Name
Eq Name =>
(Name -> Name -> Ordering)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Name)
-> (Name -> Name -> Name)
-> Ord 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
$ccompare :: Name -> Name -> Ordering
compare :: Name -> Name -> Ordering
$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
>= :: Name -> Name -> Bool
$cmax :: Name -> Name -> Name
max :: Name -> Name -> Name
$cmin :: Name -> Name -> Name
min :: Name -> Name -> Name
Ord, ReadPrec [Name]
ReadPrec Name
Int -> ReadS Name
ReadS [Name]
(Int -> ReadS Name)
-> ReadS [Name] -> ReadPrec Name -> ReadPrec [Name] -> Read Name
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Name
readsPrec :: Int -> ReadS Name
$creadList :: ReadS [Name]
readList :: ReadS [Name]
$creadPrec :: ReadPrec Name
readPrec :: ReadPrec Name
$creadListPrec :: ReadPrec [Name]
readListPrec :: ReadPrec [Name]
Read, Int -> Name -> String -> String
[Name] -> String -> String
Name -> String
(Int -> Name -> String -> String)
-> (Name -> String) -> ([Name] -> String -> String) -> Show Name
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Name -> String -> String
showsPrec :: Int -> Name -> String -> String
$cshow :: Name -> String
show :: Name -> String
$cshowList :: [Name] -> String -> String
showList :: [Name] -> String -> String
Show)
_Name :: Name
_Name = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Name")
newtype IntValue =
IntValue {
IntValue -> String
unIntValue :: String}
deriving (IntValue -> IntValue -> Bool
(IntValue -> IntValue -> Bool)
-> (IntValue -> IntValue -> Bool) -> Eq IntValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: IntValue -> IntValue -> Bool
== :: IntValue -> IntValue -> Bool
$c/= :: IntValue -> IntValue -> Bool
/= :: IntValue -> IntValue -> Bool
Eq, Eq IntValue
Eq IntValue =>
(IntValue -> IntValue -> Ordering)
-> (IntValue -> IntValue -> Bool)
-> (IntValue -> IntValue -> Bool)
-> (IntValue -> IntValue -> Bool)
-> (IntValue -> IntValue -> Bool)
-> (IntValue -> IntValue -> IntValue)
-> (IntValue -> IntValue -> IntValue)
-> Ord 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
$ccompare :: IntValue -> IntValue -> Ordering
compare :: IntValue -> IntValue -> Ordering
$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
>= :: IntValue -> IntValue -> Bool
$cmax :: IntValue -> IntValue -> IntValue
max :: IntValue -> IntValue -> IntValue
$cmin :: IntValue -> IntValue -> IntValue
min :: IntValue -> IntValue -> IntValue
Ord, ReadPrec [IntValue]
ReadPrec IntValue
Int -> ReadS IntValue
ReadS [IntValue]
(Int -> ReadS IntValue)
-> ReadS [IntValue]
-> ReadPrec IntValue
-> ReadPrec [IntValue]
-> Read IntValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS IntValue
readsPrec :: Int -> ReadS IntValue
$creadList :: ReadS [IntValue]
readList :: ReadS [IntValue]
$creadPrec :: ReadPrec IntValue
readPrec :: ReadPrec IntValue
$creadListPrec :: ReadPrec [IntValue]
readListPrec :: ReadPrec [IntValue]
Read, Int -> IntValue -> String -> String
[IntValue] -> String -> String
IntValue -> String
(Int -> IntValue -> String -> String)
-> (IntValue -> String)
-> ([IntValue] -> String -> String)
-> Show IntValue
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> IntValue -> String -> String
showsPrec :: Int -> IntValue -> String -> String
$cshow :: IntValue -> String
show :: IntValue -> String
$cshowList :: [IntValue] -> String -> String
showList :: [IntValue] -> String -> String
Show)
_IntValue :: Name
_IntValue = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.IntValue")
newtype FloatValue =
FloatValue {
FloatValue -> String
unFloatValue :: String}
deriving (FloatValue -> FloatValue -> Bool
(FloatValue -> FloatValue -> Bool)
-> (FloatValue -> FloatValue -> Bool) -> Eq FloatValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FloatValue -> FloatValue -> Bool
== :: FloatValue -> FloatValue -> Bool
$c/= :: FloatValue -> FloatValue -> Bool
/= :: FloatValue -> FloatValue -> Bool
Eq, Eq FloatValue
Eq FloatValue =>
(FloatValue -> FloatValue -> Ordering)
-> (FloatValue -> FloatValue -> Bool)
-> (FloatValue -> FloatValue -> Bool)
-> (FloatValue -> FloatValue -> Bool)
-> (FloatValue -> FloatValue -> Bool)
-> (FloatValue -> FloatValue -> FloatValue)
-> (FloatValue -> FloatValue -> FloatValue)
-> Ord 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
$ccompare :: FloatValue -> FloatValue -> Ordering
compare :: FloatValue -> FloatValue -> Ordering
$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
>= :: FloatValue -> FloatValue -> Bool
$cmax :: FloatValue -> FloatValue -> FloatValue
max :: FloatValue -> FloatValue -> FloatValue
$cmin :: FloatValue -> FloatValue -> FloatValue
min :: FloatValue -> FloatValue -> FloatValue
Ord, ReadPrec [FloatValue]
ReadPrec FloatValue
Int -> ReadS FloatValue
ReadS [FloatValue]
(Int -> ReadS FloatValue)
-> ReadS [FloatValue]
-> ReadPrec FloatValue
-> ReadPrec [FloatValue]
-> Read FloatValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FloatValue
readsPrec :: Int -> ReadS FloatValue
$creadList :: ReadS [FloatValue]
readList :: ReadS [FloatValue]
$creadPrec :: ReadPrec FloatValue
readPrec :: ReadPrec FloatValue
$creadListPrec :: ReadPrec [FloatValue]
readListPrec :: ReadPrec [FloatValue]
Read, Int -> FloatValue -> String -> String
[FloatValue] -> String -> String
FloatValue -> String
(Int -> FloatValue -> String -> String)
-> (FloatValue -> String)
-> ([FloatValue] -> String -> String)
-> Show FloatValue
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> FloatValue -> String -> String
showsPrec :: Int -> FloatValue -> String -> String
$cshow :: FloatValue -> String
show :: FloatValue -> String
$cshowList :: [FloatValue] -> String -> String
showList :: [FloatValue] -> String -> String
Show)
_FloatValue :: Name
_FloatValue = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.FloatValue")
newtype StringValue =
StringValue {
StringValue -> String
unStringValue :: String}
deriving (StringValue -> StringValue -> Bool
(StringValue -> StringValue -> Bool)
-> (StringValue -> StringValue -> Bool) -> Eq StringValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: StringValue -> StringValue -> Bool
== :: StringValue -> StringValue -> Bool
$c/= :: StringValue -> StringValue -> Bool
/= :: StringValue -> StringValue -> Bool
Eq, Eq StringValue
Eq StringValue =>
(StringValue -> StringValue -> Ordering)
-> (StringValue -> StringValue -> Bool)
-> (StringValue -> StringValue -> Bool)
-> (StringValue -> StringValue -> Bool)
-> (StringValue -> StringValue -> Bool)
-> (StringValue -> StringValue -> StringValue)
-> (StringValue -> StringValue -> StringValue)
-> Ord 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
$ccompare :: StringValue -> StringValue -> Ordering
compare :: StringValue -> StringValue -> Ordering
$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
>= :: StringValue -> StringValue -> Bool
$cmax :: StringValue -> StringValue -> StringValue
max :: StringValue -> StringValue -> StringValue
$cmin :: StringValue -> StringValue -> StringValue
min :: StringValue -> StringValue -> StringValue
Ord, ReadPrec [StringValue]
ReadPrec StringValue
Int -> ReadS StringValue
ReadS [StringValue]
(Int -> ReadS StringValue)
-> ReadS [StringValue]
-> ReadPrec StringValue
-> ReadPrec [StringValue]
-> Read StringValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS StringValue
readsPrec :: Int -> ReadS StringValue
$creadList :: ReadS [StringValue]
readList :: ReadS [StringValue]
$creadPrec :: ReadPrec StringValue
readPrec :: ReadPrec StringValue
$creadListPrec :: ReadPrec [StringValue]
readListPrec :: ReadPrec [StringValue]
Read, Int -> StringValue -> String -> String
[StringValue] -> String -> String
StringValue -> String
(Int -> StringValue -> String -> String)
-> (StringValue -> String)
-> ([StringValue] -> String -> String)
-> Show StringValue
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> StringValue -> String -> String
showsPrec :: Int -> StringValue -> String -> String
$cshow :: StringValue -> String
show :: StringValue -> String
$cshowList :: [StringValue] -> String -> String
showList :: [StringValue] -> String -> String
Show)
_StringValue :: Name
_StringValue = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.StringValue")
newtype Document =
Document {
Document -> [Definition]
unDocument :: [Definition]}
deriving (Document -> Document -> Bool
(Document -> Document -> Bool)
-> (Document -> Document -> Bool) -> Eq Document
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Document -> Document -> Bool
== :: Document -> Document -> Bool
$c/= :: Document -> Document -> Bool
/= :: Document -> Document -> Bool
Eq, Eq Document
Eq Document =>
(Document -> Document -> Ordering)
-> (Document -> Document -> Bool)
-> (Document -> Document -> Bool)
-> (Document -> Document -> Bool)
-> (Document -> Document -> Bool)
-> (Document -> Document -> Document)
-> (Document -> Document -> Document)
-> Ord 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
$ccompare :: Document -> Document -> Ordering
compare :: Document -> Document -> Ordering
$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
>= :: Document -> Document -> Bool
$cmax :: Document -> Document -> Document
max :: Document -> Document -> Document
$cmin :: Document -> Document -> Document
min :: Document -> Document -> Document
Ord, ReadPrec [Document]
ReadPrec Document
Int -> ReadS Document
ReadS [Document]
(Int -> ReadS Document)
-> ReadS [Document]
-> ReadPrec Document
-> ReadPrec [Document]
-> Read Document
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Document
readsPrec :: Int -> ReadS Document
$creadList :: ReadS [Document]
readList :: ReadS [Document]
$creadPrec :: ReadPrec Document
readPrec :: ReadPrec Document
$creadListPrec :: ReadPrec [Document]
readListPrec :: ReadPrec [Document]
Read, Int -> Document -> String -> String
[Document] -> String -> String
Document -> String
(Int -> Document -> String -> String)
-> (Document -> String)
-> ([Document] -> String -> String)
-> Show Document
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Document -> String -> String
showsPrec :: Int -> Document -> String -> String
$cshow :: Document -> String
show :: Document -> String
$cshowList :: [Document] -> String -> String
showList :: [Document] -> String -> String
Show)
_Document :: Name
_Document = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Document")
data Definition =
DefinitionExecutable ExecutableDefinition |
DefinitionTypeSystem TypeSystemDefinitionOrExtension
deriving (Definition -> Definition -> Bool
(Definition -> Definition -> Bool)
-> (Definition -> Definition -> Bool) -> Eq Definition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Definition -> Definition -> Bool
== :: Definition -> Definition -> Bool
$c/= :: Definition -> Definition -> Bool
/= :: Definition -> Definition -> Bool
Eq, Eq Definition
Eq Definition =>
(Definition -> Definition -> Ordering)
-> (Definition -> Definition -> Bool)
-> (Definition -> Definition -> Bool)
-> (Definition -> Definition -> Bool)
-> (Definition -> Definition -> Bool)
-> (Definition -> Definition -> Definition)
-> (Definition -> Definition -> Definition)
-> Ord 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
$ccompare :: Definition -> Definition -> Ordering
compare :: Definition -> Definition -> Ordering
$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
>= :: Definition -> Definition -> Bool
$cmax :: Definition -> Definition -> Definition
max :: Definition -> Definition -> Definition
$cmin :: Definition -> Definition -> Definition
min :: Definition -> Definition -> Definition
Ord, ReadPrec [Definition]
ReadPrec Definition
Int -> ReadS Definition
ReadS [Definition]
(Int -> ReadS Definition)
-> ReadS [Definition]
-> ReadPrec Definition
-> ReadPrec [Definition]
-> Read Definition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Definition
readsPrec :: Int -> ReadS Definition
$creadList :: ReadS [Definition]
readList :: ReadS [Definition]
$creadPrec :: ReadPrec Definition
readPrec :: ReadPrec Definition
$creadListPrec :: ReadPrec [Definition]
readListPrec :: ReadPrec [Definition]
Read, Int -> Definition -> String -> String
[Definition] -> String -> String
Definition -> String
(Int -> Definition -> String -> String)
-> (Definition -> String)
-> ([Definition] -> String -> String)
-> Show Definition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Definition -> String -> String
showsPrec :: Int -> Definition -> String -> String
$cshow :: Definition -> String
show :: Definition -> String
$cshowList :: [Definition] -> String -> String
showList :: [Definition] -> String -> String
Show)
_Definition :: Name
_Definition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Definition")
_Definition_executable :: Name
_Definition_executable = (String -> Name
Core.Name String
"executable")
_Definition_typeSystem :: Name
_Definition_typeSystem = (String -> Name
Core.Name String
"typeSystem")
newtype ExecutableDocument =
ExecutableDocument {
ExecutableDocument -> [ExecutableDefinition]
unExecutableDocument :: [ExecutableDefinition]}
deriving (ExecutableDocument -> ExecutableDocument -> Bool
(ExecutableDocument -> ExecutableDocument -> Bool)
-> (ExecutableDocument -> ExecutableDocument -> Bool)
-> Eq ExecutableDocument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExecutableDocument -> ExecutableDocument -> Bool
== :: ExecutableDocument -> ExecutableDocument -> Bool
$c/= :: ExecutableDocument -> ExecutableDocument -> Bool
/= :: ExecutableDocument -> ExecutableDocument -> Bool
Eq, Eq ExecutableDocument
Eq ExecutableDocument =>
(ExecutableDocument -> ExecutableDocument -> Ordering)
-> (ExecutableDocument -> ExecutableDocument -> Bool)
-> (ExecutableDocument -> ExecutableDocument -> Bool)
-> (ExecutableDocument -> ExecutableDocument -> Bool)
-> (ExecutableDocument -> ExecutableDocument -> Bool)
-> (ExecutableDocument -> ExecutableDocument -> ExecutableDocument)
-> (ExecutableDocument -> ExecutableDocument -> ExecutableDocument)
-> Ord 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
$ccompare :: ExecutableDocument -> ExecutableDocument -> Ordering
compare :: ExecutableDocument -> ExecutableDocument -> Ordering
$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
>= :: ExecutableDocument -> ExecutableDocument -> Bool
$cmax :: ExecutableDocument -> ExecutableDocument -> ExecutableDocument
max :: ExecutableDocument -> ExecutableDocument -> ExecutableDocument
$cmin :: ExecutableDocument -> ExecutableDocument -> ExecutableDocument
min :: ExecutableDocument -> ExecutableDocument -> ExecutableDocument
Ord, ReadPrec [ExecutableDocument]
ReadPrec ExecutableDocument
Int -> ReadS ExecutableDocument
ReadS [ExecutableDocument]
(Int -> ReadS ExecutableDocument)
-> ReadS [ExecutableDocument]
-> ReadPrec ExecutableDocument
-> ReadPrec [ExecutableDocument]
-> Read ExecutableDocument
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ExecutableDocument
readsPrec :: Int -> ReadS ExecutableDocument
$creadList :: ReadS [ExecutableDocument]
readList :: ReadS [ExecutableDocument]
$creadPrec :: ReadPrec ExecutableDocument
readPrec :: ReadPrec ExecutableDocument
$creadListPrec :: ReadPrec [ExecutableDocument]
readListPrec :: ReadPrec [ExecutableDocument]
Read, Int -> ExecutableDocument -> String -> String
[ExecutableDocument] -> String -> String
ExecutableDocument -> String
(Int -> ExecutableDocument -> String -> String)
-> (ExecutableDocument -> String)
-> ([ExecutableDocument] -> String -> String)
-> Show ExecutableDocument
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ExecutableDocument -> String -> String
showsPrec :: Int -> ExecutableDocument -> String -> String
$cshow :: ExecutableDocument -> String
show :: ExecutableDocument -> String
$cshowList :: [ExecutableDocument] -> String -> String
showList :: [ExecutableDocument] -> String -> String
Show)
_ExecutableDocument :: Name
_ExecutableDocument = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ExecutableDocument")
data ExecutableDefinition =
ExecutableDefinitionOperation OperationDefinition |
ExecutableDefinitionFragment FragmentDefinition
deriving (ExecutableDefinition -> ExecutableDefinition -> Bool
(ExecutableDefinition -> ExecutableDefinition -> Bool)
-> (ExecutableDefinition -> ExecutableDefinition -> Bool)
-> Eq ExecutableDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExecutableDefinition -> ExecutableDefinition -> Bool
== :: ExecutableDefinition -> ExecutableDefinition -> Bool
$c/= :: ExecutableDefinition -> ExecutableDefinition -> Bool
/= :: ExecutableDefinition -> ExecutableDefinition -> Bool
Eq, Eq ExecutableDefinition
Eq ExecutableDefinition =>
(ExecutableDefinition -> ExecutableDefinition -> Ordering)
-> (ExecutableDefinition -> ExecutableDefinition -> Bool)
-> (ExecutableDefinition -> ExecutableDefinition -> Bool)
-> (ExecutableDefinition -> ExecutableDefinition -> Bool)
-> (ExecutableDefinition -> ExecutableDefinition -> Bool)
-> (ExecutableDefinition
-> ExecutableDefinition -> ExecutableDefinition)
-> (ExecutableDefinition
-> ExecutableDefinition -> ExecutableDefinition)
-> Ord 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
$ccompare :: ExecutableDefinition -> ExecutableDefinition -> Ordering
compare :: ExecutableDefinition -> ExecutableDefinition -> Ordering
$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
>= :: ExecutableDefinition -> ExecutableDefinition -> Bool
$cmax :: ExecutableDefinition
-> ExecutableDefinition -> ExecutableDefinition
max :: ExecutableDefinition
-> ExecutableDefinition -> ExecutableDefinition
$cmin :: ExecutableDefinition
-> ExecutableDefinition -> ExecutableDefinition
min :: ExecutableDefinition
-> ExecutableDefinition -> ExecutableDefinition
Ord, ReadPrec [ExecutableDefinition]
ReadPrec ExecutableDefinition
Int -> ReadS ExecutableDefinition
ReadS [ExecutableDefinition]
(Int -> ReadS ExecutableDefinition)
-> ReadS [ExecutableDefinition]
-> ReadPrec ExecutableDefinition
-> ReadPrec [ExecutableDefinition]
-> Read ExecutableDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ExecutableDefinition
readsPrec :: Int -> ReadS ExecutableDefinition
$creadList :: ReadS [ExecutableDefinition]
readList :: ReadS [ExecutableDefinition]
$creadPrec :: ReadPrec ExecutableDefinition
readPrec :: ReadPrec ExecutableDefinition
$creadListPrec :: ReadPrec [ExecutableDefinition]
readListPrec :: ReadPrec [ExecutableDefinition]
Read, Int -> ExecutableDefinition -> String -> String
[ExecutableDefinition] -> String -> String
ExecutableDefinition -> String
(Int -> ExecutableDefinition -> String -> String)
-> (ExecutableDefinition -> String)
-> ([ExecutableDefinition] -> String -> String)
-> Show ExecutableDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ExecutableDefinition -> String -> String
showsPrec :: Int -> ExecutableDefinition -> String -> String
$cshow :: ExecutableDefinition -> String
show :: ExecutableDefinition -> String
$cshowList :: [ExecutableDefinition] -> String -> String
showList :: [ExecutableDefinition] -> String -> String
Show)
_ExecutableDefinition :: Name
_ExecutableDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ExecutableDefinition")
_ExecutableDefinition_operation :: Name
_ExecutableDefinition_operation = (String -> Name
Core.Name String
"operation")
_ExecutableDefinition_fragment :: Name
_ExecutableDefinition_fragment = (String -> Name
Core.Name String
"fragment")
data OperationDefinition =
OperationDefinitionSequence OperationDefinition_Sequence |
OperationDefinitionSelectionSet SelectionSet
deriving (OperationDefinition -> OperationDefinition -> Bool
(OperationDefinition -> OperationDefinition -> Bool)
-> (OperationDefinition -> OperationDefinition -> Bool)
-> Eq OperationDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OperationDefinition -> OperationDefinition -> Bool
== :: OperationDefinition -> OperationDefinition -> Bool
$c/= :: OperationDefinition -> OperationDefinition -> Bool
/= :: OperationDefinition -> OperationDefinition -> Bool
Eq, Eq OperationDefinition
Eq OperationDefinition =>
(OperationDefinition -> OperationDefinition -> Ordering)
-> (OperationDefinition -> OperationDefinition -> Bool)
-> (OperationDefinition -> OperationDefinition -> Bool)
-> (OperationDefinition -> OperationDefinition -> Bool)
-> (OperationDefinition -> OperationDefinition -> Bool)
-> (OperationDefinition
-> OperationDefinition -> OperationDefinition)
-> (OperationDefinition
-> OperationDefinition -> OperationDefinition)
-> Ord 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
$ccompare :: OperationDefinition -> OperationDefinition -> Ordering
compare :: OperationDefinition -> OperationDefinition -> Ordering
$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
>= :: OperationDefinition -> OperationDefinition -> Bool
$cmax :: OperationDefinition -> OperationDefinition -> OperationDefinition
max :: OperationDefinition -> OperationDefinition -> OperationDefinition
$cmin :: OperationDefinition -> OperationDefinition -> OperationDefinition
min :: OperationDefinition -> OperationDefinition -> OperationDefinition
Ord, ReadPrec [OperationDefinition]
ReadPrec OperationDefinition
Int -> ReadS OperationDefinition
ReadS [OperationDefinition]
(Int -> ReadS OperationDefinition)
-> ReadS [OperationDefinition]
-> ReadPrec OperationDefinition
-> ReadPrec [OperationDefinition]
-> Read OperationDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS OperationDefinition
readsPrec :: Int -> ReadS OperationDefinition
$creadList :: ReadS [OperationDefinition]
readList :: ReadS [OperationDefinition]
$creadPrec :: ReadPrec OperationDefinition
readPrec :: ReadPrec OperationDefinition
$creadListPrec :: ReadPrec [OperationDefinition]
readListPrec :: ReadPrec [OperationDefinition]
Read, Int -> OperationDefinition -> String -> String
[OperationDefinition] -> String -> String
OperationDefinition -> String
(Int -> OperationDefinition -> String -> String)
-> (OperationDefinition -> String)
-> ([OperationDefinition] -> String -> String)
-> Show OperationDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> OperationDefinition -> String -> String
showsPrec :: Int -> OperationDefinition -> String -> String
$cshow :: OperationDefinition -> String
show :: OperationDefinition -> String
$cshowList :: [OperationDefinition] -> String -> String
showList :: [OperationDefinition] -> String -> String
Show)
_OperationDefinition :: Name
_OperationDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.OperationDefinition")
_OperationDefinition_sequence :: Name
_OperationDefinition_sequence = (String -> Name
Core.Name String
"sequence")
_OperationDefinition_selectionSet :: Name
_OperationDefinition_selectionSet = (String -> Name
Core.Name 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
(OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool)
-> (OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool)
-> Eq OperationDefinition_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
== :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
$c/= :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
/= :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
Eq, Eq OperationDefinition_Sequence
Eq OperationDefinition_Sequence =>
(OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Ordering)
-> (OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool)
-> (OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool)
-> (OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool)
-> (OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool)
-> (OperationDefinition_Sequence
-> OperationDefinition_Sequence -> OperationDefinition_Sequence)
-> (OperationDefinition_Sequence
-> OperationDefinition_Sequence -> OperationDefinition_Sequence)
-> Ord 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
$ccompare :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Ordering
compare :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Ordering
$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
>= :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> Bool
$cmax :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> OperationDefinition_Sequence
max :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> OperationDefinition_Sequence
$cmin :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> OperationDefinition_Sequence
min :: OperationDefinition_Sequence
-> OperationDefinition_Sequence -> OperationDefinition_Sequence
Ord, ReadPrec [OperationDefinition_Sequence]
ReadPrec OperationDefinition_Sequence
Int -> ReadS OperationDefinition_Sequence
ReadS [OperationDefinition_Sequence]
(Int -> ReadS OperationDefinition_Sequence)
-> ReadS [OperationDefinition_Sequence]
-> ReadPrec OperationDefinition_Sequence
-> ReadPrec [OperationDefinition_Sequence]
-> Read OperationDefinition_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS OperationDefinition_Sequence
readsPrec :: Int -> ReadS OperationDefinition_Sequence
$creadList :: ReadS [OperationDefinition_Sequence]
readList :: ReadS [OperationDefinition_Sequence]
$creadPrec :: ReadPrec OperationDefinition_Sequence
readPrec :: ReadPrec OperationDefinition_Sequence
$creadListPrec :: ReadPrec [OperationDefinition_Sequence]
readListPrec :: ReadPrec [OperationDefinition_Sequence]
Read, Int -> OperationDefinition_Sequence -> String -> String
[OperationDefinition_Sequence] -> String -> String
OperationDefinition_Sequence -> String
(Int -> OperationDefinition_Sequence -> String -> String)
-> (OperationDefinition_Sequence -> String)
-> ([OperationDefinition_Sequence] -> String -> String)
-> Show OperationDefinition_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> OperationDefinition_Sequence -> String -> String
showsPrec :: Int -> OperationDefinition_Sequence -> String -> String
$cshow :: OperationDefinition_Sequence -> String
show :: OperationDefinition_Sequence -> String
$cshowList :: [OperationDefinition_Sequence] -> String -> String
showList :: [OperationDefinition_Sequence] -> String -> String
Show)
_OperationDefinition_Sequence :: Name
_OperationDefinition_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.OperationDefinition.Sequence")
_OperationDefinition_Sequence_operationType :: Name
_OperationDefinition_Sequence_operationType = (String -> Name
Core.Name String
"operationType")
_OperationDefinition_Sequence_name :: Name
_OperationDefinition_Sequence_name = (String -> Name
Core.Name String
"name")
_OperationDefinition_Sequence_variablesDefinition :: Name
_OperationDefinition_Sequence_variablesDefinition = (String -> Name
Core.Name String
"variablesDefinition")
_OperationDefinition_Sequence_directives :: Name
_OperationDefinition_Sequence_directives = (String -> Name
Core.Name String
"directives")
_OperationDefinition_Sequence_selectionSet :: Name
_OperationDefinition_Sequence_selectionSet = (String -> Name
Core.Name String
"selectionSet")
data OperationType =
OperationTypeQuery |
OperationTypeMutation |
OperationTypeSubscription
deriving (OperationType -> OperationType -> Bool
(OperationType -> OperationType -> Bool)
-> (OperationType -> OperationType -> Bool) -> Eq OperationType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: OperationType -> OperationType -> Bool
== :: OperationType -> OperationType -> Bool
$c/= :: OperationType -> OperationType -> Bool
/= :: OperationType -> OperationType -> Bool
Eq, Eq OperationType
Eq OperationType =>
(OperationType -> OperationType -> Ordering)
-> (OperationType -> OperationType -> Bool)
-> (OperationType -> OperationType -> Bool)
-> (OperationType -> OperationType -> Bool)
-> (OperationType -> OperationType -> Bool)
-> (OperationType -> OperationType -> OperationType)
-> (OperationType -> OperationType -> OperationType)
-> Ord 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
$ccompare :: OperationType -> OperationType -> Ordering
compare :: OperationType -> OperationType -> Ordering
$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
>= :: OperationType -> OperationType -> Bool
$cmax :: OperationType -> OperationType -> OperationType
max :: OperationType -> OperationType -> OperationType
$cmin :: OperationType -> OperationType -> OperationType
min :: OperationType -> OperationType -> OperationType
Ord, ReadPrec [OperationType]
ReadPrec OperationType
Int -> ReadS OperationType
ReadS [OperationType]
(Int -> ReadS OperationType)
-> ReadS [OperationType]
-> ReadPrec OperationType
-> ReadPrec [OperationType]
-> Read OperationType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS OperationType
readsPrec :: Int -> ReadS OperationType
$creadList :: ReadS [OperationType]
readList :: ReadS [OperationType]
$creadPrec :: ReadPrec OperationType
readPrec :: ReadPrec OperationType
$creadListPrec :: ReadPrec [OperationType]
readListPrec :: ReadPrec [OperationType]
Read, Int -> OperationType -> String -> String
[OperationType] -> String -> String
OperationType -> String
(Int -> OperationType -> String -> String)
-> (OperationType -> String)
-> ([OperationType] -> String -> String)
-> Show OperationType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> OperationType -> String -> String
showsPrec :: Int -> OperationType -> String -> String
$cshow :: OperationType -> String
show :: OperationType -> String
$cshowList :: [OperationType] -> String -> String
showList :: [OperationType] -> String -> String
Show)
_OperationType :: Name
_OperationType = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.OperationType")
_OperationType_query :: Name
_OperationType_query = (String -> Name
Core.Name String
"query")
_OperationType_mutation :: Name
_OperationType_mutation = (String -> Name
Core.Name String
"mutation")
_OperationType_subscription :: Name
_OperationType_subscription = (String -> Name
Core.Name String
"subscription")
newtype SelectionSet =
SelectionSet {
SelectionSet -> [Selection]
unSelectionSet :: [Selection]}
deriving (SelectionSet -> SelectionSet -> Bool
(SelectionSet -> SelectionSet -> Bool)
-> (SelectionSet -> SelectionSet -> Bool) -> Eq SelectionSet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SelectionSet -> SelectionSet -> Bool
== :: SelectionSet -> SelectionSet -> Bool
$c/= :: SelectionSet -> SelectionSet -> Bool
/= :: SelectionSet -> SelectionSet -> Bool
Eq, Eq SelectionSet
Eq SelectionSet =>
(SelectionSet -> SelectionSet -> Ordering)
-> (SelectionSet -> SelectionSet -> Bool)
-> (SelectionSet -> SelectionSet -> Bool)
-> (SelectionSet -> SelectionSet -> Bool)
-> (SelectionSet -> SelectionSet -> Bool)
-> (SelectionSet -> SelectionSet -> SelectionSet)
-> (SelectionSet -> SelectionSet -> SelectionSet)
-> Ord 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
$ccompare :: SelectionSet -> SelectionSet -> Ordering
compare :: SelectionSet -> SelectionSet -> Ordering
$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
>= :: SelectionSet -> SelectionSet -> Bool
$cmax :: SelectionSet -> SelectionSet -> SelectionSet
max :: SelectionSet -> SelectionSet -> SelectionSet
$cmin :: SelectionSet -> SelectionSet -> SelectionSet
min :: SelectionSet -> SelectionSet -> SelectionSet
Ord, ReadPrec [SelectionSet]
ReadPrec SelectionSet
Int -> ReadS SelectionSet
ReadS [SelectionSet]
(Int -> ReadS SelectionSet)
-> ReadS [SelectionSet]
-> ReadPrec SelectionSet
-> ReadPrec [SelectionSet]
-> Read SelectionSet
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SelectionSet
readsPrec :: Int -> ReadS SelectionSet
$creadList :: ReadS [SelectionSet]
readList :: ReadS [SelectionSet]
$creadPrec :: ReadPrec SelectionSet
readPrec :: ReadPrec SelectionSet
$creadListPrec :: ReadPrec [SelectionSet]
readListPrec :: ReadPrec [SelectionSet]
Read, Int -> SelectionSet -> String -> String
[SelectionSet] -> String -> String
SelectionSet -> String
(Int -> SelectionSet -> String -> String)
-> (SelectionSet -> String)
-> ([SelectionSet] -> String -> String)
-> Show SelectionSet
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> SelectionSet -> String -> String
showsPrec :: Int -> SelectionSet -> String -> String
$cshow :: SelectionSet -> String
show :: SelectionSet -> String
$cshowList :: [SelectionSet] -> String -> String
showList :: [SelectionSet] -> String -> String
Show)
_SelectionSet :: Name
_SelectionSet = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.SelectionSet")
data Selection =
SelectionField Field |
SelectionFragmentSpread FragmentSpread |
SelectionInlineFragment InlineFragment
deriving (Selection -> Selection -> Bool
(Selection -> Selection -> Bool)
-> (Selection -> Selection -> Bool) -> Eq Selection
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Selection -> Selection -> Bool
== :: Selection -> Selection -> Bool
$c/= :: Selection -> Selection -> Bool
/= :: Selection -> Selection -> Bool
Eq, Eq Selection
Eq Selection =>
(Selection -> Selection -> Ordering)
-> (Selection -> Selection -> Bool)
-> (Selection -> Selection -> Bool)
-> (Selection -> Selection -> Bool)
-> (Selection -> Selection -> Bool)
-> (Selection -> Selection -> Selection)
-> (Selection -> Selection -> Selection)
-> Ord 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
$ccompare :: Selection -> Selection -> Ordering
compare :: Selection -> Selection -> Ordering
$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
>= :: Selection -> Selection -> Bool
$cmax :: Selection -> Selection -> Selection
max :: Selection -> Selection -> Selection
$cmin :: Selection -> Selection -> Selection
min :: Selection -> Selection -> Selection
Ord, ReadPrec [Selection]
ReadPrec Selection
Int -> ReadS Selection
ReadS [Selection]
(Int -> ReadS Selection)
-> ReadS [Selection]
-> ReadPrec Selection
-> ReadPrec [Selection]
-> Read Selection
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Selection
readsPrec :: Int -> ReadS Selection
$creadList :: ReadS [Selection]
readList :: ReadS [Selection]
$creadPrec :: ReadPrec Selection
readPrec :: ReadPrec Selection
$creadListPrec :: ReadPrec [Selection]
readListPrec :: ReadPrec [Selection]
Read, Int -> Selection -> String -> String
[Selection] -> String -> String
Selection -> String
(Int -> Selection -> String -> String)
-> (Selection -> String)
-> ([Selection] -> String -> String)
-> Show Selection
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Selection -> String -> String
showsPrec :: Int -> Selection -> String -> String
$cshow :: Selection -> String
show :: Selection -> String
$cshowList :: [Selection] -> String -> String
showList :: [Selection] -> String -> String
Show)
_Selection :: Name
_Selection = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Selection")
_Selection_field :: Name
_Selection_field = (String -> Name
Core.Name String
"field")
_Selection_fragmentSpread :: Name
_Selection_fragmentSpread = (String -> Name
Core.Name String
"fragmentSpread")
_Selection_inlineFragment :: Name
_Selection_inlineFragment = (String -> Name
Core.Name 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
(Field -> Field -> Bool) -> (Field -> Field -> Bool) -> Eq Field
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Field -> Field -> Bool
== :: Field -> Field -> Bool
$c/= :: Field -> Field -> Bool
/= :: Field -> Field -> Bool
Eq, Eq Field
Eq Field =>
(Field -> Field -> Ordering)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Bool)
-> (Field -> Field -> Field)
-> (Field -> Field -> Field)
-> Ord 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
$ccompare :: Field -> Field -> Ordering
compare :: Field -> Field -> Ordering
$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
>= :: Field -> Field -> Bool
$cmax :: Field -> Field -> Field
max :: Field -> Field -> Field
$cmin :: Field -> Field -> Field
min :: Field -> Field -> Field
Ord, ReadPrec [Field]
ReadPrec Field
Int -> ReadS Field
ReadS [Field]
(Int -> ReadS Field)
-> ReadS [Field]
-> ReadPrec Field
-> ReadPrec [Field]
-> Read Field
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Field
readsPrec :: Int -> ReadS Field
$creadList :: ReadS [Field]
readList :: ReadS [Field]
$creadPrec :: ReadPrec Field
readPrec :: ReadPrec Field
$creadListPrec :: ReadPrec [Field]
readListPrec :: ReadPrec [Field]
Read, Int -> Field -> String -> String
[Field] -> String -> String
Field -> String
(Int -> Field -> String -> String)
-> (Field -> String) -> ([Field] -> String -> String) -> Show Field
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Field -> String -> String
showsPrec :: Int -> Field -> String -> String
$cshow :: Field -> String
show :: Field -> String
$cshowList :: [Field] -> String -> String
showList :: [Field] -> String -> String
Show)
_Field :: Name
_Field = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Field")
_Field_alias :: Name
_Field_alias = (String -> Name
Core.Name String
"alias")
_Field_name :: Name
_Field_name = (String -> Name
Core.Name String
"name")
_Field_arguments :: Name
_Field_arguments = (String -> Name
Core.Name String
"arguments")
_Field_directives :: Name
_Field_directives = (String -> Name
Core.Name String
"directives")
_Field_selectionSet :: Name
_Field_selectionSet = (String -> Name
Core.Name String
"selectionSet")
data Alias =
AliasName Name |
AliasColon
deriving (Alias -> Alias -> Bool
(Alias -> Alias -> Bool) -> (Alias -> Alias -> Bool) -> Eq Alias
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Alias -> Alias -> Bool
== :: Alias -> Alias -> Bool
$c/= :: Alias -> Alias -> Bool
/= :: Alias -> Alias -> Bool
Eq, Eq Alias
Eq Alias =>
(Alias -> Alias -> Ordering)
-> (Alias -> Alias -> Bool)
-> (Alias -> Alias -> Bool)
-> (Alias -> Alias -> Bool)
-> (Alias -> Alias -> Bool)
-> (Alias -> Alias -> Alias)
-> (Alias -> Alias -> Alias)
-> Ord 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
$ccompare :: Alias -> Alias -> Ordering
compare :: Alias -> Alias -> Ordering
$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
>= :: Alias -> Alias -> Bool
$cmax :: Alias -> Alias -> Alias
max :: Alias -> Alias -> Alias
$cmin :: Alias -> Alias -> Alias
min :: Alias -> Alias -> Alias
Ord, ReadPrec [Alias]
ReadPrec Alias
Int -> ReadS Alias
ReadS [Alias]
(Int -> ReadS Alias)
-> ReadS [Alias]
-> ReadPrec Alias
-> ReadPrec [Alias]
-> Read Alias
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Alias
readsPrec :: Int -> ReadS Alias
$creadList :: ReadS [Alias]
readList :: ReadS [Alias]
$creadPrec :: ReadPrec Alias
readPrec :: ReadPrec Alias
$creadListPrec :: ReadPrec [Alias]
readListPrec :: ReadPrec [Alias]
Read, Int -> Alias -> String -> String
[Alias] -> String -> String
Alias -> String
(Int -> Alias -> String -> String)
-> (Alias -> String) -> ([Alias] -> String -> String) -> Show Alias
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Alias -> String -> String
showsPrec :: Int -> Alias -> String -> String
$cshow :: Alias -> String
show :: Alias -> String
$cshowList :: [Alias] -> String -> String
showList :: [Alias] -> String -> String
Show)
_Alias :: Name
_Alias = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Alias")
_Alias_name :: Name
_Alias_name = (String -> Name
Core.Name String
"name")
_Alias_colon :: Name
_Alias_colon = (String -> Name
Core.Name String
"colon")
newtype Arguments =
Arguments {
Arguments -> [Argument]
unArguments :: [Argument]}
deriving (Arguments -> Arguments -> Bool
(Arguments -> Arguments -> Bool)
-> (Arguments -> Arguments -> Bool) -> Eq Arguments
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Arguments -> Arguments -> Bool
== :: Arguments -> Arguments -> Bool
$c/= :: Arguments -> Arguments -> Bool
/= :: Arguments -> Arguments -> Bool
Eq, Eq Arguments
Eq Arguments =>
(Arguments -> Arguments -> Ordering)
-> (Arguments -> Arguments -> Bool)
-> (Arguments -> Arguments -> Bool)
-> (Arguments -> Arguments -> Bool)
-> (Arguments -> Arguments -> Bool)
-> (Arguments -> Arguments -> Arguments)
-> (Arguments -> Arguments -> Arguments)
-> Ord 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
$ccompare :: Arguments -> Arguments -> Ordering
compare :: Arguments -> Arguments -> Ordering
$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
>= :: Arguments -> Arguments -> Bool
$cmax :: Arguments -> Arguments -> Arguments
max :: Arguments -> Arguments -> Arguments
$cmin :: Arguments -> Arguments -> Arguments
min :: Arguments -> Arguments -> Arguments
Ord, ReadPrec [Arguments]
ReadPrec Arguments
Int -> ReadS Arguments
ReadS [Arguments]
(Int -> ReadS Arguments)
-> ReadS [Arguments]
-> ReadPrec Arguments
-> ReadPrec [Arguments]
-> Read Arguments
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Arguments
readsPrec :: Int -> ReadS Arguments
$creadList :: ReadS [Arguments]
readList :: ReadS [Arguments]
$creadPrec :: ReadPrec Arguments
readPrec :: ReadPrec Arguments
$creadListPrec :: ReadPrec [Arguments]
readListPrec :: ReadPrec [Arguments]
Read, Int -> Arguments -> String -> String
[Arguments] -> String -> String
Arguments -> String
(Int -> Arguments -> String -> String)
-> (Arguments -> String)
-> ([Arguments] -> String -> String)
-> Show Arguments
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Arguments -> String -> String
showsPrec :: Int -> Arguments -> String -> String
$cshow :: Arguments -> String
show :: Arguments -> String
$cshowList :: [Arguments] -> String -> String
showList :: [Arguments] -> String -> String
Show)
_Arguments :: Name
_Arguments = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Arguments")
data Argument =
Argument {
Argument -> Name
argumentName :: Name,
Argument -> Value
argumentValue :: Value}
deriving (Argument -> Argument -> Bool
(Argument -> Argument -> Bool)
-> (Argument -> Argument -> Bool) -> Eq Argument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Argument -> Argument -> Bool
== :: Argument -> Argument -> Bool
$c/= :: Argument -> Argument -> Bool
/= :: Argument -> Argument -> Bool
Eq, Eq Argument
Eq Argument =>
(Argument -> Argument -> Ordering)
-> (Argument -> Argument -> Bool)
-> (Argument -> Argument -> Bool)
-> (Argument -> Argument -> Bool)
-> (Argument -> Argument -> Bool)
-> (Argument -> Argument -> Argument)
-> (Argument -> Argument -> Argument)
-> Ord 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
$ccompare :: Argument -> Argument -> Ordering
compare :: Argument -> Argument -> Ordering
$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
>= :: Argument -> Argument -> Bool
$cmax :: Argument -> Argument -> Argument
max :: Argument -> Argument -> Argument
$cmin :: Argument -> Argument -> Argument
min :: Argument -> Argument -> Argument
Ord, ReadPrec [Argument]
ReadPrec Argument
Int -> ReadS Argument
ReadS [Argument]
(Int -> ReadS Argument)
-> ReadS [Argument]
-> ReadPrec Argument
-> ReadPrec [Argument]
-> Read Argument
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Argument
readsPrec :: Int -> ReadS Argument
$creadList :: ReadS [Argument]
readList :: ReadS [Argument]
$creadPrec :: ReadPrec Argument
readPrec :: ReadPrec Argument
$creadListPrec :: ReadPrec [Argument]
readListPrec :: ReadPrec [Argument]
Read, Int -> Argument -> String -> String
[Argument] -> String -> String
Argument -> String
(Int -> Argument -> String -> String)
-> (Argument -> String)
-> ([Argument] -> String -> String)
-> Show Argument
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Argument -> String -> String
showsPrec :: Int -> Argument -> String -> String
$cshow :: Argument -> String
show :: Argument -> String
$cshowList :: [Argument] -> String -> String
showList :: [Argument] -> String -> String
Show)
_Argument :: Name
_Argument = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Argument")
_Argument_name :: Name
_Argument_name = (String -> Name
Core.Name String
"name")
_Argument_value :: Name
_Argument_value = (String -> Name
Core.Name String
"value")
data FragmentSpread =
FragmentSpread {
FragmentSpread -> FragmentName
fragmentSpreadFragmentName :: FragmentName,
FragmentSpread -> Maybe Directives
fragmentSpreadDirectives :: (Maybe Directives)}
deriving (FragmentSpread -> FragmentSpread -> Bool
(FragmentSpread -> FragmentSpread -> Bool)
-> (FragmentSpread -> FragmentSpread -> Bool) -> Eq FragmentSpread
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FragmentSpread -> FragmentSpread -> Bool
== :: FragmentSpread -> FragmentSpread -> Bool
$c/= :: FragmentSpread -> FragmentSpread -> Bool
/= :: FragmentSpread -> FragmentSpread -> Bool
Eq, Eq FragmentSpread
Eq FragmentSpread =>
(FragmentSpread -> FragmentSpread -> Ordering)
-> (FragmentSpread -> FragmentSpread -> Bool)
-> (FragmentSpread -> FragmentSpread -> Bool)
-> (FragmentSpread -> FragmentSpread -> Bool)
-> (FragmentSpread -> FragmentSpread -> Bool)
-> (FragmentSpread -> FragmentSpread -> FragmentSpread)
-> (FragmentSpread -> FragmentSpread -> FragmentSpread)
-> Ord 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
$ccompare :: FragmentSpread -> FragmentSpread -> Ordering
compare :: FragmentSpread -> FragmentSpread -> Ordering
$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
>= :: FragmentSpread -> FragmentSpread -> Bool
$cmax :: FragmentSpread -> FragmentSpread -> FragmentSpread
max :: FragmentSpread -> FragmentSpread -> FragmentSpread
$cmin :: FragmentSpread -> FragmentSpread -> FragmentSpread
min :: FragmentSpread -> FragmentSpread -> FragmentSpread
Ord, ReadPrec [FragmentSpread]
ReadPrec FragmentSpread
Int -> ReadS FragmentSpread
ReadS [FragmentSpread]
(Int -> ReadS FragmentSpread)
-> ReadS [FragmentSpread]
-> ReadPrec FragmentSpread
-> ReadPrec [FragmentSpread]
-> Read FragmentSpread
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FragmentSpread
readsPrec :: Int -> ReadS FragmentSpread
$creadList :: ReadS [FragmentSpread]
readList :: ReadS [FragmentSpread]
$creadPrec :: ReadPrec FragmentSpread
readPrec :: ReadPrec FragmentSpread
$creadListPrec :: ReadPrec [FragmentSpread]
readListPrec :: ReadPrec [FragmentSpread]
Read, Int -> FragmentSpread -> String -> String
[FragmentSpread] -> String -> String
FragmentSpread -> String
(Int -> FragmentSpread -> String -> String)
-> (FragmentSpread -> String)
-> ([FragmentSpread] -> String -> String)
-> Show FragmentSpread
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> FragmentSpread -> String -> String
showsPrec :: Int -> FragmentSpread -> String -> String
$cshow :: FragmentSpread -> String
show :: FragmentSpread -> String
$cshowList :: [FragmentSpread] -> String -> String
showList :: [FragmentSpread] -> String -> String
Show)
_FragmentSpread :: Name
_FragmentSpread = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.FragmentSpread")
_FragmentSpread_fragmentName :: Name
_FragmentSpread_fragmentName = (String -> Name
Core.Name String
"fragmentName")
_FragmentSpread_directives :: Name
_FragmentSpread_directives = (String -> Name
Core.Name 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
(InlineFragment -> InlineFragment -> Bool)
-> (InlineFragment -> InlineFragment -> Bool) -> Eq InlineFragment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InlineFragment -> InlineFragment -> Bool
== :: InlineFragment -> InlineFragment -> Bool
$c/= :: InlineFragment -> InlineFragment -> Bool
/= :: InlineFragment -> InlineFragment -> Bool
Eq, Eq InlineFragment
Eq InlineFragment =>
(InlineFragment -> InlineFragment -> Ordering)
-> (InlineFragment -> InlineFragment -> Bool)
-> (InlineFragment -> InlineFragment -> Bool)
-> (InlineFragment -> InlineFragment -> Bool)
-> (InlineFragment -> InlineFragment -> Bool)
-> (InlineFragment -> InlineFragment -> InlineFragment)
-> (InlineFragment -> InlineFragment -> InlineFragment)
-> Ord 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
$ccompare :: InlineFragment -> InlineFragment -> Ordering
compare :: InlineFragment -> InlineFragment -> Ordering
$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
>= :: InlineFragment -> InlineFragment -> Bool
$cmax :: InlineFragment -> InlineFragment -> InlineFragment
max :: InlineFragment -> InlineFragment -> InlineFragment
$cmin :: InlineFragment -> InlineFragment -> InlineFragment
min :: InlineFragment -> InlineFragment -> InlineFragment
Ord, ReadPrec [InlineFragment]
ReadPrec InlineFragment
Int -> ReadS InlineFragment
ReadS [InlineFragment]
(Int -> ReadS InlineFragment)
-> ReadS [InlineFragment]
-> ReadPrec InlineFragment
-> ReadPrec [InlineFragment]
-> Read InlineFragment
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InlineFragment
readsPrec :: Int -> ReadS InlineFragment
$creadList :: ReadS [InlineFragment]
readList :: ReadS [InlineFragment]
$creadPrec :: ReadPrec InlineFragment
readPrec :: ReadPrec InlineFragment
$creadListPrec :: ReadPrec [InlineFragment]
readListPrec :: ReadPrec [InlineFragment]
Read, Int -> InlineFragment -> String -> String
[InlineFragment] -> String -> String
InlineFragment -> String
(Int -> InlineFragment -> String -> String)
-> (InlineFragment -> String)
-> ([InlineFragment] -> String -> String)
-> Show InlineFragment
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InlineFragment -> String -> String
showsPrec :: Int -> InlineFragment -> String -> String
$cshow :: InlineFragment -> String
show :: InlineFragment -> String
$cshowList :: [InlineFragment] -> String -> String
showList :: [InlineFragment] -> String -> String
Show)
_InlineFragment :: Name
_InlineFragment = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InlineFragment")
_InlineFragment_typeCondition :: Name
_InlineFragment_typeCondition = (String -> Name
Core.Name String
"typeCondition")
_InlineFragment_directives :: Name
_InlineFragment_directives = (String -> Name
Core.Name String
"directives")
_InlineFragment_selectionSet :: Name
_InlineFragment_selectionSet = (String -> Name
Core.Name 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
(FragmentDefinition -> FragmentDefinition -> Bool)
-> (FragmentDefinition -> FragmentDefinition -> Bool)
-> Eq FragmentDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FragmentDefinition -> FragmentDefinition -> Bool
== :: FragmentDefinition -> FragmentDefinition -> Bool
$c/= :: FragmentDefinition -> FragmentDefinition -> Bool
/= :: FragmentDefinition -> FragmentDefinition -> Bool
Eq, Eq FragmentDefinition
Eq FragmentDefinition =>
(FragmentDefinition -> FragmentDefinition -> Ordering)
-> (FragmentDefinition -> FragmentDefinition -> Bool)
-> (FragmentDefinition -> FragmentDefinition -> Bool)
-> (FragmentDefinition -> FragmentDefinition -> Bool)
-> (FragmentDefinition -> FragmentDefinition -> Bool)
-> (FragmentDefinition -> FragmentDefinition -> FragmentDefinition)
-> (FragmentDefinition -> FragmentDefinition -> FragmentDefinition)
-> Ord 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
$ccompare :: FragmentDefinition -> FragmentDefinition -> Ordering
compare :: FragmentDefinition -> FragmentDefinition -> Ordering
$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
>= :: FragmentDefinition -> FragmentDefinition -> Bool
$cmax :: FragmentDefinition -> FragmentDefinition -> FragmentDefinition
max :: FragmentDefinition -> FragmentDefinition -> FragmentDefinition
$cmin :: FragmentDefinition -> FragmentDefinition -> FragmentDefinition
min :: FragmentDefinition -> FragmentDefinition -> FragmentDefinition
Ord, ReadPrec [FragmentDefinition]
ReadPrec FragmentDefinition
Int -> ReadS FragmentDefinition
ReadS [FragmentDefinition]
(Int -> ReadS FragmentDefinition)
-> ReadS [FragmentDefinition]
-> ReadPrec FragmentDefinition
-> ReadPrec [FragmentDefinition]
-> Read FragmentDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FragmentDefinition
readsPrec :: Int -> ReadS FragmentDefinition
$creadList :: ReadS [FragmentDefinition]
readList :: ReadS [FragmentDefinition]
$creadPrec :: ReadPrec FragmentDefinition
readPrec :: ReadPrec FragmentDefinition
$creadListPrec :: ReadPrec [FragmentDefinition]
readListPrec :: ReadPrec [FragmentDefinition]
Read, Int -> FragmentDefinition -> String -> String
[FragmentDefinition] -> String -> String
FragmentDefinition -> String
(Int -> FragmentDefinition -> String -> String)
-> (FragmentDefinition -> String)
-> ([FragmentDefinition] -> String -> String)
-> Show FragmentDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> FragmentDefinition -> String -> String
showsPrec :: Int -> FragmentDefinition -> String -> String
$cshow :: FragmentDefinition -> String
show :: FragmentDefinition -> String
$cshowList :: [FragmentDefinition] -> String -> String
showList :: [FragmentDefinition] -> String -> String
Show)
_FragmentDefinition :: Name
_FragmentDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.FragmentDefinition")
_FragmentDefinition_fragmentName :: Name
_FragmentDefinition_fragmentName = (String -> Name
Core.Name String
"fragmentName")
_FragmentDefinition_typeCondition :: Name
_FragmentDefinition_typeCondition = (String -> Name
Core.Name String
"typeCondition")
_FragmentDefinition_directives :: Name
_FragmentDefinition_directives = (String -> Name
Core.Name String
"directives")
_FragmentDefinition_selectionSet :: Name
_FragmentDefinition_selectionSet = (String -> Name
Core.Name String
"selectionSet")
newtype FragmentName =
FragmentName {
FragmentName -> Name
unFragmentName :: Name}
deriving (FragmentName -> FragmentName -> Bool
(FragmentName -> FragmentName -> Bool)
-> (FragmentName -> FragmentName -> Bool) -> Eq FragmentName
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FragmentName -> FragmentName -> Bool
== :: FragmentName -> FragmentName -> Bool
$c/= :: FragmentName -> FragmentName -> Bool
/= :: FragmentName -> FragmentName -> Bool
Eq, Eq FragmentName
Eq FragmentName =>
(FragmentName -> FragmentName -> Ordering)
-> (FragmentName -> FragmentName -> Bool)
-> (FragmentName -> FragmentName -> Bool)
-> (FragmentName -> FragmentName -> Bool)
-> (FragmentName -> FragmentName -> Bool)
-> (FragmentName -> FragmentName -> FragmentName)
-> (FragmentName -> FragmentName -> FragmentName)
-> Ord 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
$ccompare :: FragmentName -> FragmentName -> Ordering
compare :: FragmentName -> FragmentName -> Ordering
$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
>= :: FragmentName -> FragmentName -> Bool
$cmax :: FragmentName -> FragmentName -> FragmentName
max :: FragmentName -> FragmentName -> FragmentName
$cmin :: FragmentName -> FragmentName -> FragmentName
min :: FragmentName -> FragmentName -> FragmentName
Ord, ReadPrec [FragmentName]
ReadPrec FragmentName
Int -> ReadS FragmentName
ReadS [FragmentName]
(Int -> ReadS FragmentName)
-> ReadS [FragmentName]
-> ReadPrec FragmentName
-> ReadPrec [FragmentName]
-> Read FragmentName
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FragmentName
readsPrec :: Int -> ReadS FragmentName
$creadList :: ReadS [FragmentName]
readList :: ReadS [FragmentName]
$creadPrec :: ReadPrec FragmentName
readPrec :: ReadPrec FragmentName
$creadListPrec :: ReadPrec [FragmentName]
readListPrec :: ReadPrec [FragmentName]
Read, Int -> FragmentName -> String -> String
[FragmentName] -> String -> String
FragmentName -> String
(Int -> FragmentName -> String -> String)
-> (FragmentName -> String)
-> ([FragmentName] -> String -> String)
-> Show FragmentName
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> FragmentName -> String -> String
showsPrec :: Int -> FragmentName -> String -> String
$cshow :: FragmentName -> String
show :: FragmentName -> String
$cshowList :: [FragmentName] -> String -> String
showList :: [FragmentName] -> String -> String
Show)
_FragmentName :: Name
_FragmentName = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.FragmentName")
data TypeCondition =
TypeConditionOn |
TypeConditionNamedType NamedType
deriving (TypeCondition -> TypeCondition -> Bool
(TypeCondition -> TypeCondition -> Bool)
-> (TypeCondition -> TypeCondition -> Bool) -> Eq TypeCondition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeCondition -> TypeCondition -> Bool
== :: TypeCondition -> TypeCondition -> Bool
$c/= :: TypeCondition -> TypeCondition -> Bool
/= :: TypeCondition -> TypeCondition -> Bool
Eq, Eq TypeCondition
Eq TypeCondition =>
(TypeCondition -> TypeCondition -> Ordering)
-> (TypeCondition -> TypeCondition -> Bool)
-> (TypeCondition -> TypeCondition -> Bool)
-> (TypeCondition -> TypeCondition -> Bool)
-> (TypeCondition -> TypeCondition -> Bool)
-> (TypeCondition -> TypeCondition -> TypeCondition)
-> (TypeCondition -> TypeCondition -> TypeCondition)
-> Ord 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
$ccompare :: TypeCondition -> TypeCondition -> Ordering
compare :: TypeCondition -> TypeCondition -> Ordering
$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
>= :: TypeCondition -> TypeCondition -> Bool
$cmax :: TypeCondition -> TypeCondition -> TypeCondition
max :: TypeCondition -> TypeCondition -> TypeCondition
$cmin :: TypeCondition -> TypeCondition -> TypeCondition
min :: TypeCondition -> TypeCondition -> TypeCondition
Ord, ReadPrec [TypeCondition]
ReadPrec TypeCondition
Int -> ReadS TypeCondition
ReadS [TypeCondition]
(Int -> ReadS TypeCondition)
-> ReadS [TypeCondition]
-> ReadPrec TypeCondition
-> ReadPrec [TypeCondition]
-> Read TypeCondition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypeCondition
readsPrec :: Int -> ReadS TypeCondition
$creadList :: ReadS [TypeCondition]
readList :: ReadS [TypeCondition]
$creadPrec :: ReadPrec TypeCondition
readPrec :: ReadPrec TypeCondition
$creadListPrec :: ReadPrec [TypeCondition]
readListPrec :: ReadPrec [TypeCondition]
Read, Int -> TypeCondition -> String -> String
[TypeCondition] -> String -> String
TypeCondition -> String
(Int -> TypeCondition -> String -> String)
-> (TypeCondition -> String)
-> ([TypeCondition] -> String -> String)
-> Show TypeCondition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> TypeCondition -> String -> String
showsPrec :: Int -> TypeCondition -> String -> String
$cshow :: TypeCondition -> String
show :: TypeCondition -> String
$cshowList :: [TypeCondition] -> String -> String
showList :: [TypeCondition] -> String -> String
Show)
_TypeCondition :: Name
_TypeCondition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.TypeCondition")
_TypeCondition_on :: Name
_TypeCondition_on = (String -> Name
Core.Name String
"on")
_TypeCondition_namedType :: Name
_TypeCondition_namedType = (String -> Name
Core.Name 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
(Value -> Value -> Bool) -> (Value -> Value -> Bool) -> Eq Value
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Value -> Value -> Bool
== :: Value -> Value -> Bool
$c/= :: Value -> Value -> Bool
/= :: Value -> Value -> Bool
Eq, Eq Value
Eq Value =>
(Value -> Value -> Ordering)
-> (Value -> Value -> Bool)
-> (Value -> Value -> Bool)
-> (Value -> Value -> Bool)
-> (Value -> Value -> Bool)
-> (Value -> Value -> Value)
-> (Value -> Value -> Value)
-> Ord 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
$ccompare :: Value -> Value -> Ordering
compare :: Value -> Value -> Ordering
$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
>= :: Value -> Value -> Bool
$cmax :: Value -> Value -> Value
max :: Value -> Value -> Value
$cmin :: Value -> Value -> Value
min :: Value -> Value -> Value
Ord, ReadPrec [Value]
ReadPrec Value
Int -> ReadS Value
ReadS [Value]
(Int -> ReadS Value)
-> ReadS [Value]
-> ReadPrec Value
-> ReadPrec [Value]
-> Read Value
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Value
readsPrec :: Int -> ReadS Value
$creadList :: ReadS [Value]
readList :: ReadS [Value]
$creadPrec :: ReadPrec Value
readPrec :: ReadPrec Value
$creadListPrec :: ReadPrec [Value]
readListPrec :: ReadPrec [Value]
Read, Int -> Value -> String -> String
[Value] -> String -> String
Value -> String
(Int -> Value -> String -> String)
-> (Value -> String) -> ([Value] -> String -> String) -> Show Value
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Value -> String -> String
showsPrec :: Int -> Value -> String -> String
$cshow :: Value -> String
show :: Value -> String
$cshowList :: [Value] -> String -> String
showList :: [Value] -> String -> String
Show)
_Value :: Name
_Value = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Value")
_Value_variable :: Name
_Value_variable = (String -> Name
Core.Name String
"variable")
_Value_int :: Name
_Value_int = (String -> Name
Core.Name String
"int")
_Value_float :: Name
_Value_float = (String -> Name
Core.Name String
"float")
_Value_string :: Name
_Value_string = (String -> Name
Core.Name String
"string")
_Value_boolean :: Name
_Value_boolean = (String -> Name
Core.Name String
"boolean")
_Value_null :: Name
_Value_null = (String -> Name
Core.Name String
"null")
_Value_enum :: Name
_Value_enum = (String -> Name
Core.Name String
"enum")
_Value_list :: Name
_Value_list = (String -> Name
Core.Name String
"list")
_Value_object :: Name
_Value_object = (String -> Name
Core.Name String
"object")
data BooleanValue =
BooleanValueTrue |
BooleanValueFalse
deriving (BooleanValue -> BooleanValue -> Bool
(BooleanValue -> BooleanValue -> Bool)
-> (BooleanValue -> BooleanValue -> Bool) -> Eq BooleanValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BooleanValue -> BooleanValue -> Bool
== :: BooleanValue -> BooleanValue -> Bool
$c/= :: BooleanValue -> BooleanValue -> Bool
/= :: BooleanValue -> BooleanValue -> Bool
Eq, Eq BooleanValue
Eq BooleanValue =>
(BooleanValue -> BooleanValue -> Ordering)
-> (BooleanValue -> BooleanValue -> Bool)
-> (BooleanValue -> BooleanValue -> Bool)
-> (BooleanValue -> BooleanValue -> Bool)
-> (BooleanValue -> BooleanValue -> Bool)
-> (BooleanValue -> BooleanValue -> BooleanValue)
-> (BooleanValue -> BooleanValue -> BooleanValue)
-> Ord 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
$ccompare :: BooleanValue -> BooleanValue -> Ordering
compare :: BooleanValue -> BooleanValue -> Ordering
$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
>= :: BooleanValue -> BooleanValue -> Bool
$cmax :: BooleanValue -> BooleanValue -> BooleanValue
max :: BooleanValue -> BooleanValue -> BooleanValue
$cmin :: BooleanValue -> BooleanValue -> BooleanValue
min :: BooleanValue -> BooleanValue -> BooleanValue
Ord, ReadPrec [BooleanValue]
ReadPrec BooleanValue
Int -> ReadS BooleanValue
ReadS [BooleanValue]
(Int -> ReadS BooleanValue)
-> ReadS [BooleanValue]
-> ReadPrec BooleanValue
-> ReadPrec [BooleanValue]
-> Read BooleanValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS BooleanValue
readsPrec :: Int -> ReadS BooleanValue
$creadList :: ReadS [BooleanValue]
readList :: ReadS [BooleanValue]
$creadPrec :: ReadPrec BooleanValue
readPrec :: ReadPrec BooleanValue
$creadListPrec :: ReadPrec [BooleanValue]
readListPrec :: ReadPrec [BooleanValue]
Read, Int -> BooleanValue -> String -> String
[BooleanValue] -> String -> String
BooleanValue -> String
(Int -> BooleanValue -> String -> String)
-> (BooleanValue -> String)
-> ([BooleanValue] -> String -> String)
-> Show BooleanValue
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> BooleanValue -> String -> String
showsPrec :: Int -> BooleanValue -> String -> String
$cshow :: BooleanValue -> String
show :: BooleanValue -> String
$cshowList :: [BooleanValue] -> String -> String
showList :: [BooleanValue] -> String -> String
Show)
_BooleanValue :: Name
_BooleanValue = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.BooleanValue")
_BooleanValue_true :: Name
_BooleanValue_true = (String -> Name
Core.Name String
"true")
_BooleanValue_false :: Name
_BooleanValue_false = (String -> Name
Core.Name String
"false")
data NullValue =
NullValue {}
deriving (NullValue -> NullValue -> Bool
(NullValue -> NullValue -> Bool)
-> (NullValue -> NullValue -> Bool) -> Eq NullValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NullValue -> NullValue -> Bool
== :: NullValue -> NullValue -> Bool
$c/= :: NullValue -> NullValue -> Bool
/= :: NullValue -> NullValue -> Bool
Eq, Eq NullValue
Eq NullValue =>
(NullValue -> NullValue -> Ordering)
-> (NullValue -> NullValue -> Bool)
-> (NullValue -> NullValue -> Bool)
-> (NullValue -> NullValue -> Bool)
-> (NullValue -> NullValue -> Bool)
-> (NullValue -> NullValue -> NullValue)
-> (NullValue -> NullValue -> NullValue)
-> Ord 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
$ccompare :: NullValue -> NullValue -> Ordering
compare :: NullValue -> NullValue -> Ordering
$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
>= :: NullValue -> NullValue -> Bool
$cmax :: NullValue -> NullValue -> NullValue
max :: NullValue -> NullValue -> NullValue
$cmin :: NullValue -> NullValue -> NullValue
min :: NullValue -> NullValue -> NullValue
Ord, ReadPrec [NullValue]
ReadPrec NullValue
Int -> ReadS NullValue
ReadS [NullValue]
(Int -> ReadS NullValue)
-> ReadS [NullValue]
-> ReadPrec NullValue
-> ReadPrec [NullValue]
-> Read NullValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NullValue
readsPrec :: Int -> ReadS NullValue
$creadList :: ReadS [NullValue]
readList :: ReadS [NullValue]
$creadPrec :: ReadPrec NullValue
readPrec :: ReadPrec NullValue
$creadListPrec :: ReadPrec [NullValue]
readListPrec :: ReadPrec [NullValue]
Read, Int -> NullValue -> String -> String
[NullValue] -> String -> String
NullValue -> String
(Int -> NullValue -> String -> String)
-> (NullValue -> String)
-> ([NullValue] -> String -> String)
-> Show NullValue
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> NullValue -> String -> String
showsPrec :: Int -> NullValue -> String -> String
$cshow :: NullValue -> String
show :: NullValue -> String
$cshowList :: [NullValue] -> String -> String
showList :: [NullValue] -> String -> String
Show)
_NullValue :: Name
_NullValue = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.NullValue")
newtype EnumValue =
EnumValue {
EnumValue -> Name
unEnumValue :: Name}
deriving (EnumValue -> EnumValue -> Bool
(EnumValue -> EnumValue -> Bool)
-> (EnumValue -> EnumValue -> Bool) -> Eq EnumValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EnumValue -> EnumValue -> Bool
== :: EnumValue -> EnumValue -> Bool
$c/= :: EnumValue -> EnumValue -> Bool
/= :: EnumValue -> EnumValue -> Bool
Eq, Eq EnumValue
Eq EnumValue =>
(EnumValue -> EnumValue -> Ordering)
-> (EnumValue -> EnumValue -> Bool)
-> (EnumValue -> EnumValue -> Bool)
-> (EnumValue -> EnumValue -> Bool)
-> (EnumValue -> EnumValue -> Bool)
-> (EnumValue -> EnumValue -> EnumValue)
-> (EnumValue -> EnumValue -> EnumValue)
-> Ord 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
$ccompare :: EnumValue -> EnumValue -> Ordering
compare :: EnumValue -> EnumValue -> Ordering
$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
>= :: EnumValue -> EnumValue -> Bool
$cmax :: EnumValue -> EnumValue -> EnumValue
max :: EnumValue -> EnumValue -> EnumValue
$cmin :: EnumValue -> EnumValue -> EnumValue
min :: EnumValue -> EnumValue -> EnumValue
Ord, ReadPrec [EnumValue]
ReadPrec EnumValue
Int -> ReadS EnumValue
ReadS [EnumValue]
(Int -> ReadS EnumValue)
-> ReadS [EnumValue]
-> ReadPrec EnumValue
-> ReadPrec [EnumValue]
-> Read EnumValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EnumValue
readsPrec :: Int -> ReadS EnumValue
$creadList :: ReadS [EnumValue]
readList :: ReadS [EnumValue]
$creadPrec :: ReadPrec EnumValue
readPrec :: ReadPrec EnumValue
$creadListPrec :: ReadPrec [EnumValue]
readListPrec :: ReadPrec [EnumValue]
Read, Int -> EnumValue -> String -> String
[EnumValue] -> String -> String
EnumValue -> String
(Int -> EnumValue -> String -> String)
-> (EnumValue -> String)
-> ([EnumValue] -> String -> String)
-> Show EnumValue
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> EnumValue -> String -> String
showsPrec :: Int -> EnumValue -> String -> String
$cshow :: EnumValue -> String
show :: EnumValue -> String
$cshowList :: [EnumValue] -> String -> String
showList :: [EnumValue] -> String -> String
Show)
_EnumValue :: Name
_EnumValue = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.EnumValue")
data ListValue =
ListValueSequence ListValue_Sequence |
ListValueSequence2 [Value]
deriving (ListValue -> ListValue -> Bool
(ListValue -> ListValue -> Bool)
-> (ListValue -> ListValue -> Bool) -> Eq ListValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListValue -> ListValue -> Bool
== :: ListValue -> ListValue -> Bool
$c/= :: ListValue -> ListValue -> Bool
/= :: ListValue -> ListValue -> Bool
Eq, Eq ListValue
Eq ListValue =>
(ListValue -> ListValue -> Ordering)
-> (ListValue -> ListValue -> Bool)
-> (ListValue -> ListValue -> Bool)
-> (ListValue -> ListValue -> Bool)
-> (ListValue -> ListValue -> Bool)
-> (ListValue -> ListValue -> ListValue)
-> (ListValue -> ListValue -> ListValue)
-> Ord 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
$ccompare :: ListValue -> ListValue -> Ordering
compare :: ListValue -> ListValue -> Ordering
$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
>= :: ListValue -> ListValue -> Bool
$cmax :: ListValue -> ListValue -> ListValue
max :: ListValue -> ListValue -> ListValue
$cmin :: ListValue -> ListValue -> ListValue
min :: ListValue -> ListValue -> ListValue
Ord, ReadPrec [ListValue]
ReadPrec ListValue
Int -> ReadS ListValue
ReadS [ListValue]
(Int -> ReadS ListValue)
-> ReadS [ListValue]
-> ReadPrec ListValue
-> ReadPrec [ListValue]
-> Read ListValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ListValue
readsPrec :: Int -> ReadS ListValue
$creadList :: ReadS [ListValue]
readList :: ReadS [ListValue]
$creadPrec :: ReadPrec ListValue
readPrec :: ReadPrec ListValue
$creadListPrec :: ReadPrec [ListValue]
readListPrec :: ReadPrec [ListValue]
Read, Int -> ListValue -> String -> String
[ListValue] -> String -> String
ListValue -> String
(Int -> ListValue -> String -> String)
-> (ListValue -> String)
-> ([ListValue] -> String -> String)
-> Show ListValue
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ListValue -> String -> String
showsPrec :: Int -> ListValue -> String -> String
$cshow :: ListValue -> String
show :: ListValue -> String
$cshowList :: [ListValue] -> String -> String
showList :: [ListValue] -> String -> String
Show)
_ListValue :: Name
_ListValue = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ListValue")
_ListValue_sequence :: Name
_ListValue_sequence = (String -> Name
Core.Name String
"sequence")
_ListValue_sequence2 :: Name
_ListValue_sequence2 = (String -> Name
Core.Name String
"sequence2")
data ListValue_Sequence =
ListValue_Sequence {}
deriving (ListValue_Sequence -> ListValue_Sequence -> Bool
(ListValue_Sequence -> ListValue_Sequence -> Bool)
-> (ListValue_Sequence -> ListValue_Sequence -> Bool)
-> Eq ListValue_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListValue_Sequence -> ListValue_Sequence -> Bool
== :: ListValue_Sequence -> ListValue_Sequence -> Bool
$c/= :: ListValue_Sequence -> ListValue_Sequence -> Bool
/= :: ListValue_Sequence -> ListValue_Sequence -> Bool
Eq, Eq ListValue_Sequence
Eq ListValue_Sequence =>
(ListValue_Sequence -> ListValue_Sequence -> Ordering)
-> (ListValue_Sequence -> ListValue_Sequence -> Bool)
-> (ListValue_Sequence -> ListValue_Sequence -> Bool)
-> (ListValue_Sequence -> ListValue_Sequence -> Bool)
-> (ListValue_Sequence -> ListValue_Sequence -> Bool)
-> (ListValue_Sequence -> ListValue_Sequence -> ListValue_Sequence)
-> (ListValue_Sequence -> ListValue_Sequence -> ListValue_Sequence)
-> Ord 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
$ccompare :: ListValue_Sequence -> ListValue_Sequence -> Ordering
compare :: ListValue_Sequence -> ListValue_Sequence -> Ordering
$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
>= :: ListValue_Sequence -> ListValue_Sequence -> Bool
$cmax :: ListValue_Sequence -> ListValue_Sequence -> ListValue_Sequence
max :: ListValue_Sequence -> ListValue_Sequence -> ListValue_Sequence
$cmin :: ListValue_Sequence -> ListValue_Sequence -> ListValue_Sequence
min :: ListValue_Sequence -> ListValue_Sequence -> ListValue_Sequence
Ord, ReadPrec [ListValue_Sequence]
ReadPrec ListValue_Sequence
Int -> ReadS ListValue_Sequence
ReadS [ListValue_Sequence]
(Int -> ReadS ListValue_Sequence)
-> ReadS [ListValue_Sequence]
-> ReadPrec ListValue_Sequence
-> ReadPrec [ListValue_Sequence]
-> Read ListValue_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ListValue_Sequence
readsPrec :: Int -> ReadS ListValue_Sequence
$creadList :: ReadS [ListValue_Sequence]
readList :: ReadS [ListValue_Sequence]
$creadPrec :: ReadPrec ListValue_Sequence
readPrec :: ReadPrec ListValue_Sequence
$creadListPrec :: ReadPrec [ListValue_Sequence]
readListPrec :: ReadPrec [ListValue_Sequence]
Read, Int -> ListValue_Sequence -> String -> String
[ListValue_Sequence] -> String -> String
ListValue_Sequence -> String
(Int -> ListValue_Sequence -> String -> String)
-> (ListValue_Sequence -> String)
-> ([ListValue_Sequence] -> String -> String)
-> Show ListValue_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ListValue_Sequence -> String -> String
showsPrec :: Int -> ListValue_Sequence -> String -> String
$cshow :: ListValue_Sequence -> String
show :: ListValue_Sequence -> String
$cshowList :: [ListValue_Sequence] -> String -> String
showList :: [ListValue_Sequence] -> String -> String
Show)
_ListValue_Sequence :: Name
_ListValue_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ListValue.Sequence")
data ObjectValue =
ObjectValueSequence ObjectValue_Sequence |
ObjectValueSequence2 [ObjectField]
deriving (ObjectValue -> ObjectValue -> Bool
(ObjectValue -> ObjectValue -> Bool)
-> (ObjectValue -> ObjectValue -> Bool) -> Eq ObjectValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectValue -> ObjectValue -> Bool
== :: ObjectValue -> ObjectValue -> Bool
$c/= :: ObjectValue -> ObjectValue -> Bool
/= :: ObjectValue -> ObjectValue -> Bool
Eq, Eq ObjectValue
Eq ObjectValue =>
(ObjectValue -> ObjectValue -> Ordering)
-> (ObjectValue -> ObjectValue -> Bool)
-> (ObjectValue -> ObjectValue -> Bool)
-> (ObjectValue -> ObjectValue -> Bool)
-> (ObjectValue -> ObjectValue -> Bool)
-> (ObjectValue -> ObjectValue -> ObjectValue)
-> (ObjectValue -> ObjectValue -> ObjectValue)
-> Ord 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
$ccompare :: ObjectValue -> ObjectValue -> Ordering
compare :: ObjectValue -> ObjectValue -> Ordering
$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
>= :: ObjectValue -> ObjectValue -> Bool
$cmax :: ObjectValue -> ObjectValue -> ObjectValue
max :: ObjectValue -> ObjectValue -> ObjectValue
$cmin :: ObjectValue -> ObjectValue -> ObjectValue
min :: ObjectValue -> ObjectValue -> ObjectValue
Ord, ReadPrec [ObjectValue]
ReadPrec ObjectValue
Int -> ReadS ObjectValue
ReadS [ObjectValue]
(Int -> ReadS ObjectValue)
-> ReadS [ObjectValue]
-> ReadPrec ObjectValue
-> ReadPrec [ObjectValue]
-> Read ObjectValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectValue
readsPrec :: Int -> ReadS ObjectValue
$creadList :: ReadS [ObjectValue]
readList :: ReadS [ObjectValue]
$creadPrec :: ReadPrec ObjectValue
readPrec :: ReadPrec ObjectValue
$creadListPrec :: ReadPrec [ObjectValue]
readListPrec :: ReadPrec [ObjectValue]
Read, Int -> ObjectValue -> String -> String
[ObjectValue] -> String -> String
ObjectValue -> String
(Int -> ObjectValue -> String -> String)
-> (ObjectValue -> String)
-> ([ObjectValue] -> String -> String)
-> Show ObjectValue
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ObjectValue -> String -> String
showsPrec :: Int -> ObjectValue -> String -> String
$cshow :: ObjectValue -> String
show :: ObjectValue -> String
$cshowList :: [ObjectValue] -> String -> String
showList :: [ObjectValue] -> String -> String
Show)
_ObjectValue :: Name
_ObjectValue = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ObjectValue")
_ObjectValue_sequence :: Name
_ObjectValue_sequence = (String -> Name
Core.Name String
"sequence")
_ObjectValue_sequence2 :: Name
_ObjectValue_sequence2 = (String -> Name
Core.Name String
"sequence2")
data ObjectValue_Sequence =
ObjectValue_Sequence {}
deriving (ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
(ObjectValue_Sequence -> ObjectValue_Sequence -> Bool)
-> (ObjectValue_Sequence -> ObjectValue_Sequence -> Bool)
-> Eq ObjectValue_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
== :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
$c/= :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
/= :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
Eq, Eq ObjectValue_Sequence
Eq ObjectValue_Sequence =>
(ObjectValue_Sequence -> ObjectValue_Sequence -> Ordering)
-> (ObjectValue_Sequence -> ObjectValue_Sequence -> Bool)
-> (ObjectValue_Sequence -> ObjectValue_Sequence -> Bool)
-> (ObjectValue_Sequence -> ObjectValue_Sequence -> Bool)
-> (ObjectValue_Sequence -> ObjectValue_Sequence -> Bool)
-> (ObjectValue_Sequence
-> ObjectValue_Sequence -> ObjectValue_Sequence)
-> (ObjectValue_Sequence
-> ObjectValue_Sequence -> ObjectValue_Sequence)
-> Ord 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
$ccompare :: ObjectValue_Sequence -> ObjectValue_Sequence -> Ordering
compare :: ObjectValue_Sequence -> ObjectValue_Sequence -> Ordering
$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
>= :: ObjectValue_Sequence -> ObjectValue_Sequence -> Bool
$cmax :: ObjectValue_Sequence
-> ObjectValue_Sequence -> ObjectValue_Sequence
max :: ObjectValue_Sequence
-> ObjectValue_Sequence -> ObjectValue_Sequence
$cmin :: ObjectValue_Sequence
-> ObjectValue_Sequence -> ObjectValue_Sequence
min :: ObjectValue_Sequence
-> ObjectValue_Sequence -> ObjectValue_Sequence
Ord, ReadPrec [ObjectValue_Sequence]
ReadPrec ObjectValue_Sequence
Int -> ReadS ObjectValue_Sequence
ReadS [ObjectValue_Sequence]
(Int -> ReadS ObjectValue_Sequence)
-> ReadS [ObjectValue_Sequence]
-> ReadPrec ObjectValue_Sequence
-> ReadPrec [ObjectValue_Sequence]
-> Read ObjectValue_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectValue_Sequence
readsPrec :: Int -> ReadS ObjectValue_Sequence
$creadList :: ReadS [ObjectValue_Sequence]
readList :: ReadS [ObjectValue_Sequence]
$creadPrec :: ReadPrec ObjectValue_Sequence
readPrec :: ReadPrec ObjectValue_Sequence
$creadListPrec :: ReadPrec [ObjectValue_Sequence]
readListPrec :: ReadPrec [ObjectValue_Sequence]
Read, Int -> ObjectValue_Sequence -> String -> String
[ObjectValue_Sequence] -> String -> String
ObjectValue_Sequence -> String
(Int -> ObjectValue_Sequence -> String -> String)
-> (ObjectValue_Sequence -> String)
-> ([ObjectValue_Sequence] -> String -> String)
-> Show ObjectValue_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ObjectValue_Sequence -> String -> String
showsPrec :: Int -> ObjectValue_Sequence -> String -> String
$cshow :: ObjectValue_Sequence -> String
show :: ObjectValue_Sequence -> String
$cshowList :: [ObjectValue_Sequence] -> String -> String
showList :: [ObjectValue_Sequence] -> String -> String
Show)
_ObjectValue_Sequence :: Name
_ObjectValue_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ObjectValue.Sequence")
data ObjectField =
ObjectField {
ObjectField -> Name
objectFieldName :: Name,
ObjectField -> Value
objectFieldValue :: Value}
deriving (ObjectField -> ObjectField -> Bool
(ObjectField -> ObjectField -> Bool)
-> (ObjectField -> ObjectField -> Bool) -> Eq ObjectField
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectField -> ObjectField -> Bool
== :: ObjectField -> ObjectField -> Bool
$c/= :: ObjectField -> ObjectField -> Bool
/= :: ObjectField -> ObjectField -> Bool
Eq, Eq ObjectField
Eq ObjectField =>
(ObjectField -> ObjectField -> Ordering)
-> (ObjectField -> ObjectField -> Bool)
-> (ObjectField -> ObjectField -> Bool)
-> (ObjectField -> ObjectField -> Bool)
-> (ObjectField -> ObjectField -> Bool)
-> (ObjectField -> ObjectField -> ObjectField)
-> (ObjectField -> ObjectField -> ObjectField)
-> Ord 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
$ccompare :: ObjectField -> ObjectField -> Ordering
compare :: ObjectField -> ObjectField -> Ordering
$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
>= :: ObjectField -> ObjectField -> Bool
$cmax :: ObjectField -> ObjectField -> ObjectField
max :: ObjectField -> ObjectField -> ObjectField
$cmin :: ObjectField -> ObjectField -> ObjectField
min :: ObjectField -> ObjectField -> ObjectField
Ord, ReadPrec [ObjectField]
ReadPrec ObjectField
Int -> ReadS ObjectField
ReadS [ObjectField]
(Int -> ReadS ObjectField)
-> ReadS [ObjectField]
-> ReadPrec ObjectField
-> ReadPrec [ObjectField]
-> Read ObjectField
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectField
readsPrec :: Int -> ReadS ObjectField
$creadList :: ReadS [ObjectField]
readList :: ReadS [ObjectField]
$creadPrec :: ReadPrec ObjectField
readPrec :: ReadPrec ObjectField
$creadListPrec :: ReadPrec [ObjectField]
readListPrec :: ReadPrec [ObjectField]
Read, Int -> ObjectField -> String -> String
[ObjectField] -> String -> String
ObjectField -> String
(Int -> ObjectField -> String -> String)
-> (ObjectField -> String)
-> ([ObjectField] -> String -> String)
-> Show ObjectField
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ObjectField -> String -> String
showsPrec :: Int -> ObjectField -> String -> String
$cshow :: ObjectField -> String
show :: ObjectField -> String
$cshowList :: [ObjectField] -> String -> String
showList :: [ObjectField] -> String -> String
Show)
_ObjectField :: Name
_ObjectField = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ObjectField")
_ObjectField_name :: Name
_ObjectField_name = (String -> Name
Core.Name String
"name")
_ObjectField_value :: Name
_ObjectField_value = (String -> Name
Core.Name 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
(VariablesDefinition -> VariablesDefinition -> Bool)
-> (VariablesDefinition -> VariablesDefinition -> Bool)
-> Eq VariablesDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: VariablesDefinition -> VariablesDefinition -> Bool
== :: VariablesDefinition -> VariablesDefinition -> Bool
$c/= :: VariablesDefinition -> VariablesDefinition -> Bool
/= :: VariablesDefinition -> VariablesDefinition -> Bool
Eq, Eq VariablesDefinition
Eq VariablesDefinition =>
(VariablesDefinition -> VariablesDefinition -> Ordering)
-> (VariablesDefinition -> VariablesDefinition -> Bool)
-> (VariablesDefinition -> VariablesDefinition -> Bool)
-> (VariablesDefinition -> VariablesDefinition -> Bool)
-> (VariablesDefinition -> VariablesDefinition -> Bool)
-> (VariablesDefinition
-> VariablesDefinition -> VariablesDefinition)
-> (VariablesDefinition
-> VariablesDefinition -> VariablesDefinition)
-> Ord 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
$ccompare :: VariablesDefinition -> VariablesDefinition -> Ordering
compare :: VariablesDefinition -> VariablesDefinition -> Ordering
$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
>= :: VariablesDefinition -> VariablesDefinition -> Bool
$cmax :: VariablesDefinition -> VariablesDefinition -> VariablesDefinition
max :: VariablesDefinition -> VariablesDefinition -> VariablesDefinition
$cmin :: VariablesDefinition -> VariablesDefinition -> VariablesDefinition
min :: VariablesDefinition -> VariablesDefinition -> VariablesDefinition
Ord, ReadPrec [VariablesDefinition]
ReadPrec VariablesDefinition
Int -> ReadS VariablesDefinition
ReadS [VariablesDefinition]
(Int -> ReadS VariablesDefinition)
-> ReadS [VariablesDefinition]
-> ReadPrec VariablesDefinition
-> ReadPrec [VariablesDefinition]
-> Read VariablesDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS VariablesDefinition
readsPrec :: Int -> ReadS VariablesDefinition
$creadList :: ReadS [VariablesDefinition]
readList :: ReadS [VariablesDefinition]
$creadPrec :: ReadPrec VariablesDefinition
readPrec :: ReadPrec VariablesDefinition
$creadListPrec :: ReadPrec [VariablesDefinition]
readListPrec :: ReadPrec [VariablesDefinition]
Read, Int -> VariablesDefinition -> String -> String
[VariablesDefinition] -> String -> String
VariablesDefinition -> String
(Int -> VariablesDefinition -> String -> String)
-> (VariablesDefinition -> String)
-> ([VariablesDefinition] -> String -> String)
-> Show VariablesDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> VariablesDefinition -> String -> String
showsPrec :: Int -> VariablesDefinition -> String -> String
$cshow :: VariablesDefinition -> String
show :: VariablesDefinition -> String
$cshowList :: [VariablesDefinition] -> String -> String
showList :: [VariablesDefinition] -> String -> String
Show)
_VariablesDefinition :: Name
_VariablesDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.VariablesDefinition")
_VariablesDefinition_variable :: Name
_VariablesDefinition_variable = (String -> Name
Core.Name String
"variable")
_VariablesDefinition_type :: Name
_VariablesDefinition_type = (String -> Name
Core.Name String
"type")
_VariablesDefinition_defaultValue :: Name
_VariablesDefinition_defaultValue = (String -> Name
Core.Name String
"defaultValue")
_VariablesDefinition_directives :: Name
_VariablesDefinition_directives = (String -> Name
Core.Name String
"directives")
newtype Variable =
Variable {
Variable -> Name
unVariable :: Name}
deriving (Variable -> Variable -> Bool
(Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool) -> Eq Variable
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Variable -> Variable -> Bool
== :: Variable -> Variable -> Bool
$c/= :: Variable -> Variable -> Bool
/= :: Variable -> Variable -> Bool
Eq, Eq Variable
Eq Variable =>
(Variable -> Variable -> Ordering)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Bool)
-> (Variable -> Variable -> Variable)
-> (Variable -> Variable -> Variable)
-> Ord 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
$ccompare :: Variable -> Variable -> Ordering
compare :: Variable -> Variable -> Ordering
$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
>= :: Variable -> Variable -> Bool
$cmax :: Variable -> Variable -> Variable
max :: Variable -> Variable -> Variable
$cmin :: Variable -> Variable -> Variable
min :: Variable -> Variable -> Variable
Ord, ReadPrec [Variable]
ReadPrec Variable
Int -> ReadS Variable
ReadS [Variable]
(Int -> ReadS Variable)
-> ReadS [Variable]
-> ReadPrec Variable
-> ReadPrec [Variable]
-> Read Variable
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Variable
readsPrec :: Int -> ReadS Variable
$creadList :: ReadS [Variable]
readList :: ReadS [Variable]
$creadPrec :: ReadPrec Variable
readPrec :: ReadPrec Variable
$creadListPrec :: ReadPrec [Variable]
readListPrec :: ReadPrec [Variable]
Read, Int -> Variable -> String -> String
[Variable] -> String -> String
Variable -> String
(Int -> Variable -> String -> String)
-> (Variable -> String)
-> ([Variable] -> String -> String)
-> Show Variable
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Variable -> String -> String
showsPrec :: Int -> Variable -> String -> String
$cshow :: Variable -> String
show :: Variable -> String
$cshowList :: [Variable] -> String -> String
showList :: [Variable] -> String -> String
Show)
_Variable :: Name
_Variable = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Variable")
newtype DefaultValue =
DefaultValue {
DefaultValue -> Value
unDefaultValue :: Value}
deriving (DefaultValue -> DefaultValue -> Bool
(DefaultValue -> DefaultValue -> Bool)
-> (DefaultValue -> DefaultValue -> Bool) -> Eq DefaultValue
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DefaultValue -> DefaultValue -> Bool
== :: DefaultValue -> DefaultValue -> Bool
$c/= :: DefaultValue -> DefaultValue -> Bool
/= :: DefaultValue -> DefaultValue -> Bool
Eq, Eq DefaultValue
Eq DefaultValue =>
(DefaultValue -> DefaultValue -> Ordering)
-> (DefaultValue -> DefaultValue -> Bool)
-> (DefaultValue -> DefaultValue -> Bool)
-> (DefaultValue -> DefaultValue -> Bool)
-> (DefaultValue -> DefaultValue -> Bool)
-> (DefaultValue -> DefaultValue -> DefaultValue)
-> (DefaultValue -> DefaultValue -> DefaultValue)
-> Ord 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
$ccompare :: DefaultValue -> DefaultValue -> Ordering
compare :: DefaultValue -> DefaultValue -> Ordering
$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
>= :: DefaultValue -> DefaultValue -> Bool
$cmax :: DefaultValue -> DefaultValue -> DefaultValue
max :: DefaultValue -> DefaultValue -> DefaultValue
$cmin :: DefaultValue -> DefaultValue -> DefaultValue
min :: DefaultValue -> DefaultValue -> DefaultValue
Ord, ReadPrec [DefaultValue]
ReadPrec DefaultValue
Int -> ReadS DefaultValue
ReadS [DefaultValue]
(Int -> ReadS DefaultValue)
-> ReadS [DefaultValue]
-> ReadPrec DefaultValue
-> ReadPrec [DefaultValue]
-> Read DefaultValue
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DefaultValue
readsPrec :: Int -> ReadS DefaultValue
$creadList :: ReadS [DefaultValue]
readList :: ReadS [DefaultValue]
$creadPrec :: ReadPrec DefaultValue
readPrec :: ReadPrec DefaultValue
$creadListPrec :: ReadPrec [DefaultValue]
readListPrec :: ReadPrec [DefaultValue]
Read, Int -> DefaultValue -> String -> String
[DefaultValue] -> String -> String
DefaultValue -> String
(Int -> DefaultValue -> String -> String)
-> (DefaultValue -> String)
-> ([DefaultValue] -> String -> String)
-> Show DefaultValue
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> DefaultValue -> String -> String
showsPrec :: Int -> DefaultValue -> String -> String
$cshow :: DefaultValue -> String
show :: DefaultValue -> String
$cshowList :: [DefaultValue] -> String -> String
showList :: [DefaultValue] -> String -> String
Show)
_DefaultValue :: Name
_DefaultValue = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.DefaultValue")
data Type =
TypeNamed NamedType |
TypeList ListType |
TypeNonNull NonNullType
deriving (Type -> Type -> Bool
(Type -> Type -> Bool) -> (Type -> Type -> Bool) -> Eq Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
/= :: Type -> Type -> Bool
Eq, Eq Type
Eq Type =>
(Type -> Type -> Ordering)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Type)
-> (Type -> Type -> Type)
-> Ord 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
$ccompare :: Type -> Type -> Ordering
compare :: Type -> Type -> Ordering
$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
>= :: Type -> Type -> Bool
$cmax :: Type -> Type -> Type
max :: Type -> Type -> Type
$cmin :: Type -> Type -> Type
min :: Type -> Type -> Type
Ord, ReadPrec [Type]
ReadPrec Type
Int -> ReadS Type
ReadS [Type]
(Int -> ReadS Type)
-> ReadS [Type] -> ReadPrec Type -> ReadPrec [Type] -> Read Type
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Type
readsPrec :: Int -> ReadS Type
$creadList :: ReadS [Type]
readList :: ReadS [Type]
$creadPrec :: ReadPrec Type
readPrec :: ReadPrec Type
$creadListPrec :: ReadPrec [Type]
readListPrec :: ReadPrec [Type]
Read, Int -> Type -> String -> String
[Type] -> String -> String
Type -> String
(Int -> Type -> String -> String)
-> (Type -> String) -> ([Type] -> String -> String) -> Show Type
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Type -> String -> String
showsPrec :: Int -> Type -> String -> String
$cshow :: Type -> String
show :: Type -> String
$cshowList :: [Type] -> String -> String
showList :: [Type] -> String -> String
Show)
_Type :: Name
_Type = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Type")
_Type_named :: Name
_Type_named = (String -> Name
Core.Name String
"named")
_Type_list :: Name
_Type_list = (String -> Name
Core.Name String
"list")
_Type_nonNull :: Name
_Type_nonNull = (String -> Name
Core.Name String
"nonNull")
newtype NamedType =
NamedType {
NamedType -> Name
unNamedType :: Name}
deriving (NamedType -> NamedType -> Bool
(NamedType -> NamedType -> Bool)
-> (NamedType -> NamedType -> Bool) -> Eq NamedType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NamedType -> NamedType -> Bool
== :: NamedType -> NamedType -> Bool
$c/= :: NamedType -> NamedType -> Bool
/= :: NamedType -> NamedType -> Bool
Eq, Eq NamedType
Eq NamedType =>
(NamedType -> NamedType -> Ordering)
-> (NamedType -> NamedType -> Bool)
-> (NamedType -> NamedType -> Bool)
-> (NamedType -> NamedType -> Bool)
-> (NamedType -> NamedType -> Bool)
-> (NamedType -> NamedType -> NamedType)
-> (NamedType -> NamedType -> NamedType)
-> Ord 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
$ccompare :: NamedType -> NamedType -> Ordering
compare :: NamedType -> NamedType -> Ordering
$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
>= :: NamedType -> NamedType -> Bool
$cmax :: NamedType -> NamedType -> NamedType
max :: NamedType -> NamedType -> NamedType
$cmin :: NamedType -> NamedType -> NamedType
min :: NamedType -> NamedType -> NamedType
Ord, ReadPrec [NamedType]
ReadPrec NamedType
Int -> ReadS NamedType
ReadS [NamedType]
(Int -> ReadS NamedType)
-> ReadS [NamedType]
-> ReadPrec NamedType
-> ReadPrec [NamedType]
-> Read NamedType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NamedType
readsPrec :: Int -> ReadS NamedType
$creadList :: ReadS [NamedType]
readList :: ReadS [NamedType]
$creadPrec :: ReadPrec NamedType
readPrec :: ReadPrec NamedType
$creadListPrec :: ReadPrec [NamedType]
readListPrec :: ReadPrec [NamedType]
Read, Int -> NamedType -> String -> String
[NamedType] -> String -> String
NamedType -> String
(Int -> NamedType -> String -> String)
-> (NamedType -> String)
-> ([NamedType] -> String -> String)
-> Show NamedType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> NamedType -> String -> String
showsPrec :: Int -> NamedType -> String -> String
$cshow :: NamedType -> String
show :: NamedType -> String
$cshowList :: [NamedType] -> String -> String
showList :: [NamedType] -> String -> String
Show)
_NamedType :: Name
_NamedType = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.NamedType")
newtype ListType =
ListType {
ListType -> Type
unListType :: Type}
deriving (ListType -> ListType -> Bool
(ListType -> ListType -> Bool)
-> (ListType -> ListType -> Bool) -> Eq ListType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ListType -> ListType -> Bool
== :: ListType -> ListType -> Bool
$c/= :: ListType -> ListType -> Bool
/= :: ListType -> ListType -> Bool
Eq, Eq ListType
Eq ListType =>
(ListType -> ListType -> Ordering)
-> (ListType -> ListType -> Bool)
-> (ListType -> ListType -> Bool)
-> (ListType -> ListType -> Bool)
-> (ListType -> ListType -> Bool)
-> (ListType -> ListType -> ListType)
-> (ListType -> ListType -> ListType)
-> Ord 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
$ccompare :: ListType -> ListType -> Ordering
compare :: ListType -> ListType -> Ordering
$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
>= :: ListType -> ListType -> Bool
$cmax :: ListType -> ListType -> ListType
max :: ListType -> ListType -> ListType
$cmin :: ListType -> ListType -> ListType
min :: ListType -> ListType -> ListType
Ord, ReadPrec [ListType]
ReadPrec ListType
Int -> ReadS ListType
ReadS [ListType]
(Int -> ReadS ListType)
-> ReadS [ListType]
-> ReadPrec ListType
-> ReadPrec [ListType]
-> Read ListType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ListType
readsPrec :: Int -> ReadS ListType
$creadList :: ReadS [ListType]
readList :: ReadS [ListType]
$creadPrec :: ReadPrec ListType
readPrec :: ReadPrec ListType
$creadListPrec :: ReadPrec [ListType]
readListPrec :: ReadPrec [ListType]
Read, Int -> ListType -> String -> String
[ListType] -> String -> String
ListType -> String
(Int -> ListType -> String -> String)
-> (ListType -> String)
-> ([ListType] -> String -> String)
-> Show ListType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ListType -> String -> String
showsPrec :: Int -> ListType -> String -> String
$cshow :: ListType -> String
show :: ListType -> String
$cshowList :: [ListType] -> String -> String
showList :: [ListType] -> String -> String
Show)
_ListType :: Name
_ListType = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ListType")
data NonNullType =
NonNullTypeNamed NamedType |
NonNullTypeList ListType
deriving (NonNullType -> NonNullType -> Bool
(NonNullType -> NonNullType -> Bool)
-> (NonNullType -> NonNullType -> Bool) -> Eq NonNullType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: NonNullType -> NonNullType -> Bool
== :: NonNullType -> NonNullType -> Bool
$c/= :: NonNullType -> NonNullType -> Bool
/= :: NonNullType -> NonNullType -> Bool
Eq, Eq NonNullType
Eq NonNullType =>
(NonNullType -> NonNullType -> Ordering)
-> (NonNullType -> NonNullType -> Bool)
-> (NonNullType -> NonNullType -> Bool)
-> (NonNullType -> NonNullType -> Bool)
-> (NonNullType -> NonNullType -> Bool)
-> (NonNullType -> NonNullType -> NonNullType)
-> (NonNullType -> NonNullType -> NonNullType)
-> Ord 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
$ccompare :: NonNullType -> NonNullType -> Ordering
compare :: NonNullType -> NonNullType -> Ordering
$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
>= :: NonNullType -> NonNullType -> Bool
$cmax :: NonNullType -> NonNullType -> NonNullType
max :: NonNullType -> NonNullType -> NonNullType
$cmin :: NonNullType -> NonNullType -> NonNullType
min :: NonNullType -> NonNullType -> NonNullType
Ord, ReadPrec [NonNullType]
ReadPrec NonNullType
Int -> ReadS NonNullType
ReadS [NonNullType]
(Int -> ReadS NonNullType)
-> ReadS [NonNullType]
-> ReadPrec NonNullType
-> ReadPrec [NonNullType]
-> Read NonNullType
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS NonNullType
readsPrec :: Int -> ReadS NonNullType
$creadList :: ReadS [NonNullType]
readList :: ReadS [NonNullType]
$creadPrec :: ReadPrec NonNullType
readPrec :: ReadPrec NonNullType
$creadListPrec :: ReadPrec [NonNullType]
readListPrec :: ReadPrec [NonNullType]
Read, Int -> NonNullType -> String -> String
[NonNullType] -> String -> String
NonNullType -> String
(Int -> NonNullType -> String -> String)
-> (NonNullType -> String)
-> ([NonNullType] -> String -> String)
-> Show NonNullType
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> NonNullType -> String -> String
showsPrec :: Int -> NonNullType -> String -> String
$cshow :: NonNullType -> String
show :: NonNullType -> String
$cshowList :: [NonNullType] -> String -> String
showList :: [NonNullType] -> String -> String
Show)
_NonNullType :: Name
_NonNullType = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.NonNullType")
_NonNullType_named :: Name
_NonNullType_named = (String -> Name
Core.Name String
"named")
_NonNullType_list :: Name
_NonNullType_list = (String -> Name
Core.Name String
"list")
newtype Directives =
Directives {
Directives -> [Directive]
unDirectives :: [Directive]}
deriving (Directives -> Directives -> Bool
(Directives -> Directives -> Bool)
-> (Directives -> Directives -> Bool) -> Eq Directives
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Directives -> Directives -> Bool
== :: Directives -> Directives -> Bool
$c/= :: Directives -> Directives -> Bool
/= :: Directives -> Directives -> Bool
Eq, Eq Directives
Eq Directives =>
(Directives -> Directives -> Ordering)
-> (Directives -> Directives -> Bool)
-> (Directives -> Directives -> Bool)
-> (Directives -> Directives -> Bool)
-> (Directives -> Directives -> Bool)
-> (Directives -> Directives -> Directives)
-> (Directives -> Directives -> Directives)
-> Ord 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
$ccompare :: Directives -> Directives -> Ordering
compare :: Directives -> Directives -> Ordering
$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
>= :: Directives -> Directives -> Bool
$cmax :: Directives -> Directives -> Directives
max :: Directives -> Directives -> Directives
$cmin :: Directives -> Directives -> Directives
min :: Directives -> Directives -> Directives
Ord, ReadPrec [Directives]
ReadPrec Directives
Int -> ReadS Directives
ReadS [Directives]
(Int -> ReadS Directives)
-> ReadS [Directives]
-> ReadPrec Directives
-> ReadPrec [Directives]
-> Read Directives
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Directives
readsPrec :: Int -> ReadS Directives
$creadList :: ReadS [Directives]
readList :: ReadS [Directives]
$creadPrec :: ReadPrec Directives
readPrec :: ReadPrec Directives
$creadListPrec :: ReadPrec [Directives]
readListPrec :: ReadPrec [Directives]
Read, Int -> Directives -> String -> String
[Directives] -> String -> String
Directives -> String
(Int -> Directives -> String -> String)
-> (Directives -> String)
-> ([Directives] -> String -> String)
-> Show Directives
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Directives -> String -> String
showsPrec :: Int -> Directives -> String -> String
$cshow :: Directives -> String
show :: Directives -> String
$cshowList :: [Directives] -> String -> String
showList :: [Directives] -> String -> String
Show)
_Directives :: Name
_Directives = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Directives")
data Directive =
Directive {
Directive -> Name
directiveName :: Name,
Directive -> Maybe Arguments
directiveArguments :: (Maybe Arguments)}
deriving (Directive -> Directive -> Bool
(Directive -> Directive -> Bool)
-> (Directive -> Directive -> Bool) -> Eq Directive
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Directive -> Directive -> Bool
== :: Directive -> Directive -> Bool
$c/= :: Directive -> Directive -> Bool
/= :: Directive -> Directive -> Bool
Eq, Eq Directive
Eq Directive =>
(Directive -> Directive -> Ordering)
-> (Directive -> Directive -> Bool)
-> (Directive -> Directive -> Bool)
-> (Directive -> Directive -> Bool)
-> (Directive -> Directive -> Bool)
-> (Directive -> Directive -> Directive)
-> (Directive -> Directive -> Directive)
-> Ord 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
$ccompare :: Directive -> Directive -> Ordering
compare :: Directive -> Directive -> Ordering
$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
>= :: Directive -> Directive -> Bool
$cmax :: Directive -> Directive -> Directive
max :: Directive -> Directive -> Directive
$cmin :: Directive -> Directive -> Directive
min :: Directive -> Directive -> Directive
Ord, ReadPrec [Directive]
ReadPrec Directive
Int -> ReadS Directive
ReadS [Directive]
(Int -> ReadS Directive)
-> ReadS [Directive]
-> ReadPrec Directive
-> ReadPrec [Directive]
-> Read Directive
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Directive
readsPrec :: Int -> ReadS Directive
$creadList :: ReadS [Directive]
readList :: ReadS [Directive]
$creadPrec :: ReadPrec Directive
readPrec :: ReadPrec Directive
$creadListPrec :: ReadPrec [Directive]
readListPrec :: ReadPrec [Directive]
Read, Int -> Directive -> String -> String
[Directive] -> String -> String
Directive -> String
(Int -> Directive -> String -> String)
-> (Directive -> String)
-> ([Directive] -> String -> String)
-> Show Directive
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Directive -> String -> String
showsPrec :: Int -> Directive -> String -> String
$cshow :: Directive -> String
show :: Directive -> String
$cshowList :: [Directive] -> String -> String
showList :: [Directive] -> String -> String
Show)
_Directive :: Name
_Directive = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Directive")
_Directive_name :: Name
_Directive_name = (String -> Name
Core.Name String
"name")
_Directive_arguments :: Name
_Directive_arguments = (String -> Name
Core.Name String
"arguments")
newtype TypeSystemDocment =
TypeSystemDocment {
TypeSystemDocment -> [TypeSystemDefinition]
unTypeSystemDocment :: [TypeSystemDefinition]}
deriving (TypeSystemDocment -> TypeSystemDocment -> Bool
(TypeSystemDocment -> TypeSystemDocment -> Bool)
-> (TypeSystemDocment -> TypeSystemDocment -> Bool)
-> Eq TypeSystemDocment
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeSystemDocment -> TypeSystemDocment -> Bool
== :: TypeSystemDocment -> TypeSystemDocment -> Bool
$c/= :: TypeSystemDocment -> TypeSystemDocment -> Bool
/= :: TypeSystemDocment -> TypeSystemDocment -> Bool
Eq, Eq TypeSystemDocment
Eq TypeSystemDocment =>
(TypeSystemDocment -> TypeSystemDocment -> Ordering)
-> (TypeSystemDocment -> TypeSystemDocment -> Bool)
-> (TypeSystemDocment -> TypeSystemDocment -> Bool)
-> (TypeSystemDocment -> TypeSystemDocment -> Bool)
-> (TypeSystemDocment -> TypeSystemDocment -> Bool)
-> (TypeSystemDocment -> TypeSystemDocment -> TypeSystemDocment)
-> (TypeSystemDocment -> TypeSystemDocment -> TypeSystemDocment)
-> Ord 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
$ccompare :: TypeSystemDocment -> TypeSystemDocment -> Ordering
compare :: TypeSystemDocment -> TypeSystemDocment -> Ordering
$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
>= :: TypeSystemDocment -> TypeSystemDocment -> Bool
$cmax :: TypeSystemDocment -> TypeSystemDocment -> TypeSystemDocment
max :: TypeSystemDocment -> TypeSystemDocment -> TypeSystemDocment
$cmin :: TypeSystemDocment -> TypeSystemDocment -> TypeSystemDocment
min :: TypeSystemDocment -> TypeSystemDocment -> TypeSystemDocment
Ord, ReadPrec [TypeSystemDocment]
ReadPrec TypeSystemDocment
Int -> ReadS TypeSystemDocment
ReadS [TypeSystemDocment]
(Int -> ReadS TypeSystemDocment)
-> ReadS [TypeSystemDocment]
-> ReadPrec TypeSystemDocment
-> ReadPrec [TypeSystemDocment]
-> Read TypeSystemDocment
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypeSystemDocment
readsPrec :: Int -> ReadS TypeSystemDocment
$creadList :: ReadS [TypeSystemDocment]
readList :: ReadS [TypeSystemDocment]
$creadPrec :: ReadPrec TypeSystemDocment
readPrec :: ReadPrec TypeSystemDocment
$creadListPrec :: ReadPrec [TypeSystemDocment]
readListPrec :: ReadPrec [TypeSystemDocment]
Read, Int -> TypeSystemDocment -> String -> String
[TypeSystemDocment] -> String -> String
TypeSystemDocment -> String
(Int -> TypeSystemDocment -> String -> String)
-> (TypeSystemDocment -> String)
-> ([TypeSystemDocment] -> String -> String)
-> Show TypeSystemDocment
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> TypeSystemDocment -> String -> String
showsPrec :: Int -> TypeSystemDocment -> String -> String
$cshow :: TypeSystemDocment -> String
show :: TypeSystemDocment -> String
$cshowList :: [TypeSystemDocment] -> String -> String
showList :: [TypeSystemDocment] -> String -> String
Show)
_TypeSystemDocment :: Name
_TypeSystemDocment = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.TypeSystemDocment")
data TypeSystemDefinition =
TypeSystemDefinitionSchema SchemaDefinition |
TypeSystemDefinitionType TypeDefinition |
TypeSystemDefinitionDirective DirectiveDefinition
deriving (TypeSystemDefinition -> TypeSystemDefinition -> Bool
(TypeSystemDefinition -> TypeSystemDefinition -> Bool)
-> (TypeSystemDefinition -> TypeSystemDefinition -> Bool)
-> Eq TypeSystemDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
== :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
$c/= :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
/= :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
Eq, Eq TypeSystemDefinition
Eq TypeSystemDefinition =>
(TypeSystemDefinition -> TypeSystemDefinition -> Ordering)
-> (TypeSystemDefinition -> TypeSystemDefinition -> Bool)
-> (TypeSystemDefinition -> TypeSystemDefinition -> Bool)
-> (TypeSystemDefinition -> TypeSystemDefinition -> Bool)
-> (TypeSystemDefinition -> TypeSystemDefinition -> Bool)
-> (TypeSystemDefinition
-> TypeSystemDefinition -> TypeSystemDefinition)
-> (TypeSystemDefinition
-> TypeSystemDefinition -> TypeSystemDefinition)
-> Ord 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
$ccompare :: TypeSystemDefinition -> TypeSystemDefinition -> Ordering
compare :: TypeSystemDefinition -> TypeSystemDefinition -> Ordering
$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
>= :: TypeSystemDefinition -> TypeSystemDefinition -> Bool
$cmax :: TypeSystemDefinition
-> TypeSystemDefinition -> TypeSystemDefinition
max :: TypeSystemDefinition
-> TypeSystemDefinition -> TypeSystemDefinition
$cmin :: TypeSystemDefinition
-> TypeSystemDefinition -> TypeSystemDefinition
min :: TypeSystemDefinition
-> TypeSystemDefinition -> TypeSystemDefinition
Ord, ReadPrec [TypeSystemDefinition]
ReadPrec TypeSystemDefinition
Int -> ReadS TypeSystemDefinition
ReadS [TypeSystemDefinition]
(Int -> ReadS TypeSystemDefinition)
-> ReadS [TypeSystemDefinition]
-> ReadPrec TypeSystemDefinition
-> ReadPrec [TypeSystemDefinition]
-> Read TypeSystemDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypeSystemDefinition
readsPrec :: Int -> ReadS TypeSystemDefinition
$creadList :: ReadS [TypeSystemDefinition]
readList :: ReadS [TypeSystemDefinition]
$creadPrec :: ReadPrec TypeSystemDefinition
readPrec :: ReadPrec TypeSystemDefinition
$creadListPrec :: ReadPrec [TypeSystemDefinition]
readListPrec :: ReadPrec [TypeSystemDefinition]
Read, Int -> TypeSystemDefinition -> String -> String
[TypeSystemDefinition] -> String -> String
TypeSystemDefinition -> String
(Int -> TypeSystemDefinition -> String -> String)
-> (TypeSystemDefinition -> String)
-> ([TypeSystemDefinition] -> String -> String)
-> Show TypeSystemDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> TypeSystemDefinition -> String -> String
showsPrec :: Int -> TypeSystemDefinition -> String -> String
$cshow :: TypeSystemDefinition -> String
show :: TypeSystemDefinition -> String
$cshowList :: [TypeSystemDefinition] -> String -> String
showList :: [TypeSystemDefinition] -> String -> String
Show)
_TypeSystemDefinition :: Name
_TypeSystemDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.TypeSystemDefinition")
_TypeSystemDefinition_schema :: Name
_TypeSystemDefinition_schema = (String -> Name
Core.Name String
"schema")
_TypeSystemDefinition_type :: Name
_TypeSystemDefinition_type = (String -> Name
Core.Name String
"type")
_TypeSystemDefinition_directive :: Name
_TypeSystemDefinition_directive = (String -> Name
Core.Name String
"directive")
newtype TypeSystemExtensionDocument =
TypeSystemExtensionDocument {
TypeSystemExtensionDocument -> [TypeSystemDefinitionOrExtension]
unTypeSystemExtensionDocument :: [TypeSystemDefinitionOrExtension]}
deriving (TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
(TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> Bool)
-> (TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> Bool)
-> Eq TypeSystemExtensionDocument
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
== :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
$c/= :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
/= :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
Eq, Eq TypeSystemExtensionDocument
Eq TypeSystemExtensionDocument =>
(TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> Ordering)
-> (TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> Bool)
-> (TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> Bool)
-> (TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> Bool)
-> (TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> Bool)
-> (TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> TypeSystemExtensionDocument)
-> (TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> TypeSystemExtensionDocument)
-> Ord 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
$ccompare :: TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> Ordering
compare :: TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> Ordering
$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
>= :: TypeSystemExtensionDocument -> TypeSystemExtensionDocument -> Bool
$cmax :: TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> TypeSystemExtensionDocument
max :: TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> TypeSystemExtensionDocument
$cmin :: TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> TypeSystemExtensionDocument
min :: TypeSystemExtensionDocument
-> TypeSystemExtensionDocument -> TypeSystemExtensionDocument
Ord, ReadPrec [TypeSystemExtensionDocument]
ReadPrec TypeSystemExtensionDocument
Int -> ReadS TypeSystemExtensionDocument
ReadS [TypeSystemExtensionDocument]
(Int -> ReadS TypeSystemExtensionDocument)
-> ReadS [TypeSystemExtensionDocument]
-> ReadPrec TypeSystemExtensionDocument
-> ReadPrec [TypeSystemExtensionDocument]
-> Read TypeSystemExtensionDocument
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypeSystemExtensionDocument
readsPrec :: Int -> ReadS TypeSystemExtensionDocument
$creadList :: ReadS [TypeSystemExtensionDocument]
readList :: ReadS [TypeSystemExtensionDocument]
$creadPrec :: ReadPrec TypeSystemExtensionDocument
readPrec :: ReadPrec TypeSystemExtensionDocument
$creadListPrec :: ReadPrec [TypeSystemExtensionDocument]
readListPrec :: ReadPrec [TypeSystemExtensionDocument]
Read, Int -> TypeSystemExtensionDocument -> String -> String
[TypeSystemExtensionDocument] -> String -> String
TypeSystemExtensionDocument -> String
(Int -> TypeSystemExtensionDocument -> String -> String)
-> (TypeSystemExtensionDocument -> String)
-> ([TypeSystemExtensionDocument] -> String -> String)
-> Show TypeSystemExtensionDocument
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> TypeSystemExtensionDocument -> String -> String
showsPrec :: Int -> TypeSystemExtensionDocument -> String -> String
$cshow :: TypeSystemExtensionDocument -> String
show :: TypeSystemExtensionDocument -> String
$cshowList :: [TypeSystemExtensionDocument] -> String -> String
showList :: [TypeSystemExtensionDocument] -> String -> String
Show)
_TypeSystemExtensionDocument :: Name
_TypeSystemExtensionDocument = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.TypeSystemExtensionDocument")
data TypeSystemDefinitionOrExtension =
TypeSystemDefinitionOrExtensionDefinition TypeSystemDefinition |
TypeSystemDefinitionOrExtensionExtension TypeSystemExtension
deriving (TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
(TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool)
-> (TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool)
-> Eq TypeSystemDefinitionOrExtension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
== :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
$c/= :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
/= :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
Eq, Eq TypeSystemDefinitionOrExtension
Eq TypeSystemDefinitionOrExtension =>
(TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Ordering)
-> (TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool)
-> (TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool)
-> (TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool)
-> (TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool)
-> (TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension)
-> (TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension)
-> Ord 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
$ccompare :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Ordering
compare :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Ordering
$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
>= :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension -> Bool
$cmax :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
max :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
$cmin :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
min :: TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
-> TypeSystemDefinitionOrExtension
Ord, ReadPrec [TypeSystemDefinitionOrExtension]
ReadPrec TypeSystemDefinitionOrExtension
Int -> ReadS TypeSystemDefinitionOrExtension
ReadS [TypeSystemDefinitionOrExtension]
(Int -> ReadS TypeSystemDefinitionOrExtension)
-> ReadS [TypeSystemDefinitionOrExtension]
-> ReadPrec TypeSystemDefinitionOrExtension
-> ReadPrec [TypeSystemDefinitionOrExtension]
-> Read TypeSystemDefinitionOrExtension
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypeSystemDefinitionOrExtension
readsPrec :: Int -> ReadS TypeSystemDefinitionOrExtension
$creadList :: ReadS [TypeSystemDefinitionOrExtension]
readList :: ReadS [TypeSystemDefinitionOrExtension]
$creadPrec :: ReadPrec TypeSystemDefinitionOrExtension
readPrec :: ReadPrec TypeSystemDefinitionOrExtension
$creadListPrec :: ReadPrec [TypeSystemDefinitionOrExtension]
readListPrec :: ReadPrec [TypeSystemDefinitionOrExtension]
Read, Int -> TypeSystemDefinitionOrExtension -> String -> String
[TypeSystemDefinitionOrExtension] -> String -> String
TypeSystemDefinitionOrExtension -> String
(Int -> TypeSystemDefinitionOrExtension -> String -> String)
-> (TypeSystemDefinitionOrExtension -> String)
-> ([TypeSystemDefinitionOrExtension] -> String -> String)
-> Show TypeSystemDefinitionOrExtension
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> TypeSystemDefinitionOrExtension -> String -> String
showsPrec :: Int -> TypeSystemDefinitionOrExtension -> String -> String
$cshow :: TypeSystemDefinitionOrExtension -> String
show :: TypeSystemDefinitionOrExtension -> String
$cshowList :: [TypeSystemDefinitionOrExtension] -> String -> String
showList :: [TypeSystemDefinitionOrExtension] -> String -> String
Show)
_TypeSystemDefinitionOrExtension :: Name
_TypeSystemDefinitionOrExtension = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.TypeSystemDefinitionOrExtension")
_TypeSystemDefinitionOrExtension_definition :: Name
_TypeSystemDefinitionOrExtension_definition = (String -> Name
Core.Name String
"definition")
_TypeSystemDefinitionOrExtension_extension :: Name
_TypeSystemDefinitionOrExtension_extension = (String -> Name
Core.Name String
"extension")
data TypeSystemExtension =
TypeSystemExtensionSchema SchemaExtension |
TypeSystemExtensionType TypeExtension
deriving (TypeSystemExtension -> TypeSystemExtension -> Bool
(TypeSystemExtension -> TypeSystemExtension -> Bool)
-> (TypeSystemExtension -> TypeSystemExtension -> Bool)
-> Eq TypeSystemExtension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeSystemExtension -> TypeSystemExtension -> Bool
== :: TypeSystemExtension -> TypeSystemExtension -> Bool
$c/= :: TypeSystemExtension -> TypeSystemExtension -> Bool
/= :: TypeSystemExtension -> TypeSystemExtension -> Bool
Eq, Eq TypeSystemExtension
Eq TypeSystemExtension =>
(TypeSystemExtension -> TypeSystemExtension -> Ordering)
-> (TypeSystemExtension -> TypeSystemExtension -> Bool)
-> (TypeSystemExtension -> TypeSystemExtension -> Bool)
-> (TypeSystemExtension -> TypeSystemExtension -> Bool)
-> (TypeSystemExtension -> TypeSystemExtension -> Bool)
-> (TypeSystemExtension
-> TypeSystemExtension -> TypeSystemExtension)
-> (TypeSystemExtension
-> TypeSystemExtension -> TypeSystemExtension)
-> Ord 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
$ccompare :: TypeSystemExtension -> TypeSystemExtension -> Ordering
compare :: TypeSystemExtension -> TypeSystemExtension -> Ordering
$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
>= :: TypeSystemExtension -> TypeSystemExtension -> Bool
$cmax :: TypeSystemExtension -> TypeSystemExtension -> TypeSystemExtension
max :: TypeSystemExtension -> TypeSystemExtension -> TypeSystemExtension
$cmin :: TypeSystemExtension -> TypeSystemExtension -> TypeSystemExtension
min :: TypeSystemExtension -> TypeSystemExtension -> TypeSystemExtension
Ord, ReadPrec [TypeSystemExtension]
ReadPrec TypeSystemExtension
Int -> ReadS TypeSystemExtension
ReadS [TypeSystemExtension]
(Int -> ReadS TypeSystemExtension)
-> ReadS [TypeSystemExtension]
-> ReadPrec TypeSystemExtension
-> ReadPrec [TypeSystemExtension]
-> Read TypeSystemExtension
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypeSystemExtension
readsPrec :: Int -> ReadS TypeSystemExtension
$creadList :: ReadS [TypeSystemExtension]
readList :: ReadS [TypeSystemExtension]
$creadPrec :: ReadPrec TypeSystemExtension
readPrec :: ReadPrec TypeSystemExtension
$creadListPrec :: ReadPrec [TypeSystemExtension]
readListPrec :: ReadPrec [TypeSystemExtension]
Read, Int -> TypeSystemExtension -> String -> String
[TypeSystemExtension] -> String -> String
TypeSystemExtension -> String
(Int -> TypeSystemExtension -> String -> String)
-> (TypeSystemExtension -> String)
-> ([TypeSystemExtension] -> String -> String)
-> Show TypeSystemExtension
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> TypeSystemExtension -> String -> String
showsPrec :: Int -> TypeSystemExtension -> String -> String
$cshow :: TypeSystemExtension -> String
show :: TypeSystemExtension -> String
$cshowList :: [TypeSystemExtension] -> String -> String
showList :: [TypeSystemExtension] -> String -> String
Show)
_TypeSystemExtension :: Name
_TypeSystemExtension = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.TypeSystemExtension")
_TypeSystemExtension_schema :: Name
_TypeSystemExtension_schema = (String -> Name
Core.Name String
"schema")
_TypeSystemExtension_type :: Name
_TypeSystemExtension_type = (String -> Name
Core.Name 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
(SchemaDefinition -> SchemaDefinition -> Bool)
-> (SchemaDefinition -> SchemaDefinition -> Bool)
-> Eq SchemaDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SchemaDefinition -> SchemaDefinition -> Bool
== :: SchemaDefinition -> SchemaDefinition -> Bool
$c/= :: SchemaDefinition -> SchemaDefinition -> Bool
/= :: SchemaDefinition -> SchemaDefinition -> Bool
Eq, Eq SchemaDefinition
Eq SchemaDefinition =>
(SchemaDefinition -> SchemaDefinition -> Ordering)
-> (SchemaDefinition -> SchemaDefinition -> Bool)
-> (SchemaDefinition -> SchemaDefinition -> Bool)
-> (SchemaDefinition -> SchemaDefinition -> Bool)
-> (SchemaDefinition -> SchemaDefinition -> Bool)
-> (SchemaDefinition -> SchemaDefinition -> SchemaDefinition)
-> (SchemaDefinition -> SchemaDefinition -> SchemaDefinition)
-> Ord 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
$ccompare :: SchemaDefinition -> SchemaDefinition -> Ordering
compare :: SchemaDefinition -> SchemaDefinition -> Ordering
$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
>= :: SchemaDefinition -> SchemaDefinition -> Bool
$cmax :: SchemaDefinition -> SchemaDefinition -> SchemaDefinition
max :: SchemaDefinition -> SchemaDefinition -> SchemaDefinition
$cmin :: SchemaDefinition -> SchemaDefinition -> SchemaDefinition
min :: SchemaDefinition -> SchemaDefinition -> SchemaDefinition
Ord, ReadPrec [SchemaDefinition]
ReadPrec SchemaDefinition
Int -> ReadS SchemaDefinition
ReadS [SchemaDefinition]
(Int -> ReadS SchemaDefinition)
-> ReadS [SchemaDefinition]
-> ReadPrec SchemaDefinition
-> ReadPrec [SchemaDefinition]
-> Read SchemaDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SchemaDefinition
readsPrec :: Int -> ReadS SchemaDefinition
$creadList :: ReadS [SchemaDefinition]
readList :: ReadS [SchemaDefinition]
$creadPrec :: ReadPrec SchemaDefinition
readPrec :: ReadPrec SchemaDefinition
$creadListPrec :: ReadPrec [SchemaDefinition]
readListPrec :: ReadPrec [SchemaDefinition]
Read, Int -> SchemaDefinition -> String -> String
[SchemaDefinition] -> String -> String
SchemaDefinition -> String
(Int -> SchemaDefinition -> String -> String)
-> (SchemaDefinition -> String)
-> ([SchemaDefinition] -> String -> String)
-> Show SchemaDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> SchemaDefinition -> String -> String
showsPrec :: Int -> SchemaDefinition -> String -> String
$cshow :: SchemaDefinition -> String
show :: SchemaDefinition -> String
$cshowList :: [SchemaDefinition] -> String -> String
showList :: [SchemaDefinition] -> String -> String
Show)
_SchemaDefinition :: Name
_SchemaDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.SchemaDefinition")
_SchemaDefinition_description :: Name
_SchemaDefinition_description = (String -> Name
Core.Name String
"description")
_SchemaDefinition_directives :: Name
_SchemaDefinition_directives = (String -> Name
Core.Name String
"directives")
_SchemaDefinition_rootOperationTypeDefinition :: Name
_SchemaDefinition_rootOperationTypeDefinition = (String -> Name
Core.Name String
"rootOperationTypeDefinition")
data SchemaExtension =
SchemaExtensionSequence SchemaExtension_Sequence |
SchemaExtensionSequence2 Directives
deriving (SchemaExtension -> SchemaExtension -> Bool
(SchemaExtension -> SchemaExtension -> Bool)
-> (SchemaExtension -> SchemaExtension -> Bool)
-> Eq SchemaExtension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SchemaExtension -> SchemaExtension -> Bool
== :: SchemaExtension -> SchemaExtension -> Bool
$c/= :: SchemaExtension -> SchemaExtension -> Bool
/= :: SchemaExtension -> SchemaExtension -> Bool
Eq, Eq SchemaExtension
Eq SchemaExtension =>
(SchemaExtension -> SchemaExtension -> Ordering)
-> (SchemaExtension -> SchemaExtension -> Bool)
-> (SchemaExtension -> SchemaExtension -> Bool)
-> (SchemaExtension -> SchemaExtension -> Bool)
-> (SchemaExtension -> SchemaExtension -> Bool)
-> (SchemaExtension -> SchemaExtension -> SchemaExtension)
-> (SchemaExtension -> SchemaExtension -> SchemaExtension)
-> Ord 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
$ccompare :: SchemaExtension -> SchemaExtension -> Ordering
compare :: SchemaExtension -> SchemaExtension -> Ordering
$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
>= :: SchemaExtension -> SchemaExtension -> Bool
$cmax :: SchemaExtension -> SchemaExtension -> SchemaExtension
max :: SchemaExtension -> SchemaExtension -> SchemaExtension
$cmin :: SchemaExtension -> SchemaExtension -> SchemaExtension
min :: SchemaExtension -> SchemaExtension -> SchemaExtension
Ord, ReadPrec [SchemaExtension]
ReadPrec SchemaExtension
Int -> ReadS SchemaExtension
ReadS [SchemaExtension]
(Int -> ReadS SchemaExtension)
-> ReadS [SchemaExtension]
-> ReadPrec SchemaExtension
-> ReadPrec [SchemaExtension]
-> Read SchemaExtension
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SchemaExtension
readsPrec :: Int -> ReadS SchemaExtension
$creadList :: ReadS [SchemaExtension]
readList :: ReadS [SchemaExtension]
$creadPrec :: ReadPrec SchemaExtension
readPrec :: ReadPrec SchemaExtension
$creadListPrec :: ReadPrec [SchemaExtension]
readListPrec :: ReadPrec [SchemaExtension]
Read, Int -> SchemaExtension -> String -> String
[SchemaExtension] -> String -> String
SchemaExtension -> String
(Int -> SchemaExtension -> String -> String)
-> (SchemaExtension -> String)
-> ([SchemaExtension] -> String -> String)
-> Show SchemaExtension
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> SchemaExtension -> String -> String
showsPrec :: Int -> SchemaExtension -> String -> String
$cshow :: SchemaExtension -> String
show :: SchemaExtension -> String
$cshowList :: [SchemaExtension] -> String -> String
showList :: [SchemaExtension] -> String -> String
Show)
_SchemaExtension :: Name
_SchemaExtension = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.SchemaExtension")
_SchemaExtension_sequence :: Name
_SchemaExtension_sequence = (String -> Name
Core.Name String
"sequence")
_SchemaExtension_sequence2 :: Name
_SchemaExtension_sequence2 = (String -> Name
Core.Name 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
(SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool)
-> (SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool)
-> Eq SchemaExtension_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
== :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
$c/= :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
/= :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
Eq, Eq SchemaExtension_Sequence
Eq SchemaExtension_Sequence =>
(SchemaExtension_Sequence -> SchemaExtension_Sequence -> Ordering)
-> (SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool)
-> (SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool)
-> (SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool)
-> (SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool)
-> (SchemaExtension_Sequence
-> SchemaExtension_Sequence -> SchemaExtension_Sequence)
-> (SchemaExtension_Sequence
-> SchemaExtension_Sequence -> SchemaExtension_Sequence)
-> Ord 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
$ccompare :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Ordering
compare :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Ordering
$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
>= :: SchemaExtension_Sequence -> SchemaExtension_Sequence -> Bool
$cmax :: SchemaExtension_Sequence
-> SchemaExtension_Sequence -> SchemaExtension_Sequence
max :: SchemaExtension_Sequence
-> SchemaExtension_Sequence -> SchemaExtension_Sequence
$cmin :: SchemaExtension_Sequence
-> SchemaExtension_Sequence -> SchemaExtension_Sequence
min :: SchemaExtension_Sequence
-> SchemaExtension_Sequence -> SchemaExtension_Sequence
Ord, ReadPrec [SchemaExtension_Sequence]
ReadPrec SchemaExtension_Sequence
Int -> ReadS SchemaExtension_Sequence
ReadS [SchemaExtension_Sequence]
(Int -> ReadS SchemaExtension_Sequence)
-> ReadS [SchemaExtension_Sequence]
-> ReadPrec SchemaExtension_Sequence
-> ReadPrec [SchemaExtension_Sequence]
-> Read SchemaExtension_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS SchemaExtension_Sequence
readsPrec :: Int -> ReadS SchemaExtension_Sequence
$creadList :: ReadS [SchemaExtension_Sequence]
readList :: ReadS [SchemaExtension_Sequence]
$creadPrec :: ReadPrec SchemaExtension_Sequence
readPrec :: ReadPrec SchemaExtension_Sequence
$creadListPrec :: ReadPrec [SchemaExtension_Sequence]
readListPrec :: ReadPrec [SchemaExtension_Sequence]
Read, Int -> SchemaExtension_Sequence -> String -> String
[SchemaExtension_Sequence] -> String -> String
SchemaExtension_Sequence -> String
(Int -> SchemaExtension_Sequence -> String -> String)
-> (SchemaExtension_Sequence -> String)
-> ([SchemaExtension_Sequence] -> String -> String)
-> Show SchemaExtension_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> SchemaExtension_Sequence -> String -> String
showsPrec :: Int -> SchemaExtension_Sequence -> String -> String
$cshow :: SchemaExtension_Sequence -> String
show :: SchemaExtension_Sequence -> String
$cshowList :: [SchemaExtension_Sequence] -> String -> String
showList :: [SchemaExtension_Sequence] -> String -> String
Show)
_SchemaExtension_Sequence :: Name
_SchemaExtension_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.SchemaExtension.Sequence")
_SchemaExtension_Sequence_directives :: Name
_SchemaExtension_Sequence_directives = (String -> Name
Core.Name String
"directives")
_SchemaExtension_Sequence_rootOperationTypeDefinition :: Name
_SchemaExtension_Sequence_rootOperationTypeDefinition = (String -> Name
Core.Name String
"rootOperationTypeDefinition")
data RootOperationTypeDefinition =
RootOperationTypeDefinition {
RootOperationTypeDefinition -> OperationType
rootOperationTypeDefinitionOperationType :: OperationType,
RootOperationTypeDefinition -> NamedType
rootOperationTypeDefinitionNamedType :: NamedType}
deriving (RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
(RootOperationTypeDefinition
-> RootOperationTypeDefinition -> Bool)
-> (RootOperationTypeDefinition
-> RootOperationTypeDefinition -> Bool)
-> Eq RootOperationTypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
== :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
$c/= :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
/= :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
Eq, Eq RootOperationTypeDefinition
Eq RootOperationTypeDefinition =>
(RootOperationTypeDefinition
-> RootOperationTypeDefinition -> Ordering)
-> (RootOperationTypeDefinition
-> RootOperationTypeDefinition -> Bool)
-> (RootOperationTypeDefinition
-> RootOperationTypeDefinition -> Bool)
-> (RootOperationTypeDefinition
-> RootOperationTypeDefinition -> Bool)
-> (RootOperationTypeDefinition
-> RootOperationTypeDefinition -> Bool)
-> (RootOperationTypeDefinition
-> RootOperationTypeDefinition -> RootOperationTypeDefinition)
-> (RootOperationTypeDefinition
-> RootOperationTypeDefinition -> RootOperationTypeDefinition)
-> Ord 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
$ccompare :: RootOperationTypeDefinition
-> RootOperationTypeDefinition -> Ordering
compare :: RootOperationTypeDefinition
-> RootOperationTypeDefinition -> Ordering
$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
>= :: RootOperationTypeDefinition -> RootOperationTypeDefinition -> Bool
$cmax :: RootOperationTypeDefinition
-> RootOperationTypeDefinition -> RootOperationTypeDefinition
max :: RootOperationTypeDefinition
-> RootOperationTypeDefinition -> RootOperationTypeDefinition
$cmin :: RootOperationTypeDefinition
-> RootOperationTypeDefinition -> RootOperationTypeDefinition
min :: RootOperationTypeDefinition
-> RootOperationTypeDefinition -> RootOperationTypeDefinition
Ord, ReadPrec [RootOperationTypeDefinition]
ReadPrec RootOperationTypeDefinition
Int -> ReadS RootOperationTypeDefinition
ReadS [RootOperationTypeDefinition]
(Int -> ReadS RootOperationTypeDefinition)
-> ReadS [RootOperationTypeDefinition]
-> ReadPrec RootOperationTypeDefinition
-> ReadPrec [RootOperationTypeDefinition]
-> Read RootOperationTypeDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS RootOperationTypeDefinition
readsPrec :: Int -> ReadS RootOperationTypeDefinition
$creadList :: ReadS [RootOperationTypeDefinition]
readList :: ReadS [RootOperationTypeDefinition]
$creadPrec :: ReadPrec RootOperationTypeDefinition
readPrec :: ReadPrec RootOperationTypeDefinition
$creadListPrec :: ReadPrec [RootOperationTypeDefinition]
readListPrec :: ReadPrec [RootOperationTypeDefinition]
Read, Int -> RootOperationTypeDefinition -> String -> String
[RootOperationTypeDefinition] -> String -> String
RootOperationTypeDefinition -> String
(Int -> RootOperationTypeDefinition -> String -> String)
-> (RootOperationTypeDefinition -> String)
-> ([RootOperationTypeDefinition] -> String -> String)
-> Show RootOperationTypeDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> RootOperationTypeDefinition -> String -> String
showsPrec :: Int -> RootOperationTypeDefinition -> String -> String
$cshow :: RootOperationTypeDefinition -> String
show :: RootOperationTypeDefinition -> String
$cshowList :: [RootOperationTypeDefinition] -> String -> String
showList :: [RootOperationTypeDefinition] -> String -> String
Show)
_RootOperationTypeDefinition :: Name
_RootOperationTypeDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.RootOperationTypeDefinition")
_RootOperationTypeDefinition_operationType :: Name
_RootOperationTypeDefinition_operationType = (String -> Name
Core.Name String
"operationType")
_RootOperationTypeDefinition_namedType :: Name
_RootOperationTypeDefinition_namedType = (String -> Name
Core.Name String
"namedType")
newtype Description =
Description {
Description -> StringValue
unDescription :: StringValue}
deriving (Description -> Description -> Bool
(Description -> Description -> Bool)
-> (Description -> Description -> Bool) -> Eq Description
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Description -> Description -> Bool
== :: Description -> Description -> Bool
$c/= :: Description -> Description -> Bool
/= :: Description -> Description -> Bool
Eq, Eq Description
Eq Description =>
(Description -> Description -> Ordering)
-> (Description -> Description -> Bool)
-> (Description -> Description -> Bool)
-> (Description -> Description -> Bool)
-> (Description -> Description -> Bool)
-> (Description -> Description -> Description)
-> (Description -> Description -> Description)
-> Ord 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
$ccompare :: Description -> Description -> Ordering
compare :: Description -> Description -> Ordering
$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
>= :: Description -> Description -> Bool
$cmax :: Description -> Description -> Description
max :: Description -> Description -> Description
$cmin :: Description -> Description -> Description
min :: Description -> Description -> Description
Ord, ReadPrec [Description]
ReadPrec Description
Int -> ReadS Description
ReadS [Description]
(Int -> ReadS Description)
-> ReadS [Description]
-> ReadPrec Description
-> ReadPrec [Description]
-> Read Description
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS Description
readsPrec :: Int -> ReadS Description
$creadList :: ReadS [Description]
readList :: ReadS [Description]
$creadPrec :: ReadPrec Description
readPrec :: ReadPrec Description
$creadListPrec :: ReadPrec [Description]
readListPrec :: ReadPrec [Description]
Read, Int -> Description -> String -> String
[Description] -> String -> String
Description -> String
(Int -> Description -> String -> String)
-> (Description -> String)
-> ([Description] -> String -> String)
-> Show Description
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> Description -> String -> String
showsPrec :: Int -> Description -> String -> String
$cshow :: Description -> String
show :: Description -> String
$cshowList :: [Description] -> String -> String
showList :: [Description] -> String -> String
Show)
_Description :: Name
_Description = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.Description")
data TypeDefinition =
TypeDefinitionScalar ScalarTypeDefinition |
TypeDefinitionObject ObjectTypeDefinition |
TypeDefinitionInterface InterfaceTypeDefinition |
TypeDefinitionUnion UnionTypeDefinition |
TypeDefinitionEnum EnumTypeDefinition |
TypeDefinitionInputObject InputObjectTypeDefinition
deriving (TypeDefinition -> TypeDefinition -> Bool
(TypeDefinition -> TypeDefinition -> Bool)
-> (TypeDefinition -> TypeDefinition -> Bool) -> Eq TypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeDefinition -> TypeDefinition -> Bool
== :: TypeDefinition -> TypeDefinition -> Bool
$c/= :: TypeDefinition -> TypeDefinition -> Bool
/= :: TypeDefinition -> TypeDefinition -> Bool
Eq, Eq TypeDefinition
Eq TypeDefinition =>
(TypeDefinition -> TypeDefinition -> Ordering)
-> (TypeDefinition -> TypeDefinition -> Bool)
-> (TypeDefinition -> TypeDefinition -> Bool)
-> (TypeDefinition -> TypeDefinition -> Bool)
-> (TypeDefinition -> TypeDefinition -> Bool)
-> (TypeDefinition -> TypeDefinition -> TypeDefinition)
-> (TypeDefinition -> TypeDefinition -> TypeDefinition)
-> Ord 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
$ccompare :: TypeDefinition -> TypeDefinition -> Ordering
compare :: TypeDefinition -> TypeDefinition -> Ordering
$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
>= :: TypeDefinition -> TypeDefinition -> Bool
$cmax :: TypeDefinition -> TypeDefinition -> TypeDefinition
max :: TypeDefinition -> TypeDefinition -> TypeDefinition
$cmin :: TypeDefinition -> TypeDefinition -> TypeDefinition
min :: TypeDefinition -> TypeDefinition -> TypeDefinition
Ord, ReadPrec [TypeDefinition]
ReadPrec TypeDefinition
Int -> ReadS TypeDefinition
ReadS [TypeDefinition]
(Int -> ReadS TypeDefinition)
-> ReadS [TypeDefinition]
-> ReadPrec TypeDefinition
-> ReadPrec [TypeDefinition]
-> Read TypeDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypeDefinition
readsPrec :: Int -> ReadS TypeDefinition
$creadList :: ReadS [TypeDefinition]
readList :: ReadS [TypeDefinition]
$creadPrec :: ReadPrec TypeDefinition
readPrec :: ReadPrec TypeDefinition
$creadListPrec :: ReadPrec [TypeDefinition]
readListPrec :: ReadPrec [TypeDefinition]
Read, Int -> TypeDefinition -> String -> String
[TypeDefinition] -> String -> String
TypeDefinition -> String
(Int -> TypeDefinition -> String -> String)
-> (TypeDefinition -> String)
-> ([TypeDefinition] -> String -> String)
-> Show TypeDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> TypeDefinition -> String -> String
showsPrec :: Int -> TypeDefinition -> String -> String
$cshow :: TypeDefinition -> String
show :: TypeDefinition -> String
$cshowList :: [TypeDefinition] -> String -> String
showList :: [TypeDefinition] -> String -> String
Show)
_TypeDefinition :: Name
_TypeDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.TypeDefinition")
_TypeDefinition_scalar :: Name
_TypeDefinition_scalar = (String -> Name
Core.Name String
"scalar")
_TypeDefinition_object :: Name
_TypeDefinition_object = (String -> Name
Core.Name String
"object")
_TypeDefinition_interface :: Name
_TypeDefinition_interface = (String -> Name
Core.Name String
"interface")
_TypeDefinition_union :: Name
_TypeDefinition_union = (String -> Name
Core.Name String
"union")
_TypeDefinition_enum :: Name
_TypeDefinition_enum = (String -> Name
Core.Name String
"enum")
_TypeDefinition_inputObject :: Name
_TypeDefinition_inputObject = (String -> Name
Core.Name String
"inputObject")
data TypeExtension =
TypeExtensionScalar ScalarTypeExtension |
TypeExtensionObject ObjectTypeExtension |
TypeExtensionInterface InterfaceTypeExtension |
TypeExtensionUnion UnionTypeExtension |
TypeExtensionEnum EnumTypeExtension |
TypeExtensionInputObject InputObjectTypeExtension
deriving (TypeExtension -> TypeExtension -> Bool
(TypeExtension -> TypeExtension -> Bool)
-> (TypeExtension -> TypeExtension -> Bool) -> Eq TypeExtension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeExtension -> TypeExtension -> Bool
== :: TypeExtension -> TypeExtension -> Bool
$c/= :: TypeExtension -> TypeExtension -> Bool
/= :: TypeExtension -> TypeExtension -> Bool
Eq, Eq TypeExtension
Eq TypeExtension =>
(TypeExtension -> TypeExtension -> Ordering)
-> (TypeExtension -> TypeExtension -> Bool)
-> (TypeExtension -> TypeExtension -> Bool)
-> (TypeExtension -> TypeExtension -> Bool)
-> (TypeExtension -> TypeExtension -> Bool)
-> (TypeExtension -> TypeExtension -> TypeExtension)
-> (TypeExtension -> TypeExtension -> TypeExtension)
-> Ord 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
$ccompare :: TypeExtension -> TypeExtension -> Ordering
compare :: TypeExtension -> TypeExtension -> Ordering
$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
>= :: TypeExtension -> TypeExtension -> Bool
$cmax :: TypeExtension -> TypeExtension -> TypeExtension
max :: TypeExtension -> TypeExtension -> TypeExtension
$cmin :: TypeExtension -> TypeExtension -> TypeExtension
min :: TypeExtension -> TypeExtension -> TypeExtension
Ord, ReadPrec [TypeExtension]
ReadPrec TypeExtension
Int -> ReadS TypeExtension
ReadS [TypeExtension]
(Int -> ReadS TypeExtension)
-> ReadS [TypeExtension]
-> ReadPrec TypeExtension
-> ReadPrec [TypeExtension]
-> Read TypeExtension
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypeExtension
readsPrec :: Int -> ReadS TypeExtension
$creadList :: ReadS [TypeExtension]
readList :: ReadS [TypeExtension]
$creadPrec :: ReadPrec TypeExtension
readPrec :: ReadPrec TypeExtension
$creadListPrec :: ReadPrec [TypeExtension]
readListPrec :: ReadPrec [TypeExtension]
Read, Int -> TypeExtension -> String -> String
[TypeExtension] -> String -> String
TypeExtension -> String
(Int -> TypeExtension -> String -> String)
-> (TypeExtension -> String)
-> ([TypeExtension] -> String -> String)
-> Show TypeExtension
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> TypeExtension -> String -> String
showsPrec :: Int -> TypeExtension -> String -> String
$cshow :: TypeExtension -> String
show :: TypeExtension -> String
$cshowList :: [TypeExtension] -> String -> String
showList :: [TypeExtension] -> String -> String
Show)
_TypeExtension :: Name
_TypeExtension = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.TypeExtension")
_TypeExtension_scalar :: Name
_TypeExtension_scalar = (String -> Name
Core.Name String
"scalar")
_TypeExtension_object :: Name
_TypeExtension_object = (String -> Name
Core.Name String
"object")
_TypeExtension_interface :: Name
_TypeExtension_interface = (String -> Name
Core.Name String
"interface")
_TypeExtension_union :: Name
_TypeExtension_union = (String -> Name
Core.Name String
"union")
_TypeExtension_enum :: Name
_TypeExtension_enum = (String -> Name
Core.Name String
"enum")
_TypeExtension_inputObject :: Name
_TypeExtension_inputObject = (String -> Name
Core.Name 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
(ScalarTypeDefinition -> ScalarTypeDefinition -> Bool)
-> (ScalarTypeDefinition -> ScalarTypeDefinition -> Bool)
-> Eq ScalarTypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
== :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
$c/= :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
/= :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
Eq, Eq ScalarTypeDefinition
Eq ScalarTypeDefinition =>
(ScalarTypeDefinition -> ScalarTypeDefinition -> Ordering)
-> (ScalarTypeDefinition -> ScalarTypeDefinition -> Bool)
-> (ScalarTypeDefinition -> ScalarTypeDefinition -> Bool)
-> (ScalarTypeDefinition -> ScalarTypeDefinition -> Bool)
-> (ScalarTypeDefinition -> ScalarTypeDefinition -> Bool)
-> (ScalarTypeDefinition
-> ScalarTypeDefinition -> ScalarTypeDefinition)
-> (ScalarTypeDefinition
-> ScalarTypeDefinition -> ScalarTypeDefinition)
-> Ord 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
$ccompare :: ScalarTypeDefinition -> ScalarTypeDefinition -> Ordering
compare :: ScalarTypeDefinition -> ScalarTypeDefinition -> Ordering
$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
>= :: ScalarTypeDefinition -> ScalarTypeDefinition -> Bool
$cmax :: ScalarTypeDefinition
-> ScalarTypeDefinition -> ScalarTypeDefinition
max :: ScalarTypeDefinition
-> ScalarTypeDefinition -> ScalarTypeDefinition
$cmin :: ScalarTypeDefinition
-> ScalarTypeDefinition -> ScalarTypeDefinition
min :: ScalarTypeDefinition
-> ScalarTypeDefinition -> ScalarTypeDefinition
Ord, ReadPrec [ScalarTypeDefinition]
ReadPrec ScalarTypeDefinition
Int -> ReadS ScalarTypeDefinition
ReadS [ScalarTypeDefinition]
(Int -> ReadS ScalarTypeDefinition)
-> ReadS [ScalarTypeDefinition]
-> ReadPrec ScalarTypeDefinition
-> ReadPrec [ScalarTypeDefinition]
-> Read ScalarTypeDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ScalarTypeDefinition
readsPrec :: Int -> ReadS ScalarTypeDefinition
$creadList :: ReadS [ScalarTypeDefinition]
readList :: ReadS [ScalarTypeDefinition]
$creadPrec :: ReadPrec ScalarTypeDefinition
readPrec :: ReadPrec ScalarTypeDefinition
$creadListPrec :: ReadPrec [ScalarTypeDefinition]
readListPrec :: ReadPrec [ScalarTypeDefinition]
Read, Int -> ScalarTypeDefinition -> String -> String
[ScalarTypeDefinition] -> String -> String
ScalarTypeDefinition -> String
(Int -> ScalarTypeDefinition -> String -> String)
-> (ScalarTypeDefinition -> String)
-> ([ScalarTypeDefinition] -> String -> String)
-> Show ScalarTypeDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ScalarTypeDefinition -> String -> String
showsPrec :: Int -> ScalarTypeDefinition -> String -> String
$cshow :: ScalarTypeDefinition -> String
show :: ScalarTypeDefinition -> String
$cshowList :: [ScalarTypeDefinition] -> String -> String
showList :: [ScalarTypeDefinition] -> String -> String
Show)
_ScalarTypeDefinition :: Name
_ScalarTypeDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ScalarTypeDefinition")
_ScalarTypeDefinition_description :: Name
_ScalarTypeDefinition_description = (String -> Name
Core.Name String
"description")
_ScalarTypeDefinition_name :: Name
_ScalarTypeDefinition_name = (String -> Name
Core.Name String
"name")
_ScalarTypeDefinition_directives :: Name
_ScalarTypeDefinition_directives = (String -> Name
Core.Name String
"directives")
data ScalarTypeExtension =
ScalarTypeExtension {
ScalarTypeExtension -> Name
scalarTypeExtensionName :: Name,
ScalarTypeExtension -> Directives
scalarTypeExtensionDirectives :: Directives}
deriving (ScalarTypeExtension -> ScalarTypeExtension -> Bool
(ScalarTypeExtension -> ScalarTypeExtension -> Bool)
-> (ScalarTypeExtension -> ScalarTypeExtension -> Bool)
-> Eq ScalarTypeExtension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
== :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
$c/= :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
/= :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
Eq, Eq ScalarTypeExtension
Eq ScalarTypeExtension =>
(ScalarTypeExtension -> ScalarTypeExtension -> Ordering)
-> (ScalarTypeExtension -> ScalarTypeExtension -> Bool)
-> (ScalarTypeExtension -> ScalarTypeExtension -> Bool)
-> (ScalarTypeExtension -> ScalarTypeExtension -> Bool)
-> (ScalarTypeExtension -> ScalarTypeExtension -> Bool)
-> (ScalarTypeExtension
-> ScalarTypeExtension -> ScalarTypeExtension)
-> (ScalarTypeExtension
-> ScalarTypeExtension -> ScalarTypeExtension)
-> Ord 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
$ccompare :: ScalarTypeExtension -> ScalarTypeExtension -> Ordering
compare :: ScalarTypeExtension -> ScalarTypeExtension -> Ordering
$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
>= :: ScalarTypeExtension -> ScalarTypeExtension -> Bool
$cmax :: ScalarTypeExtension -> ScalarTypeExtension -> ScalarTypeExtension
max :: ScalarTypeExtension -> ScalarTypeExtension -> ScalarTypeExtension
$cmin :: ScalarTypeExtension -> ScalarTypeExtension -> ScalarTypeExtension
min :: ScalarTypeExtension -> ScalarTypeExtension -> ScalarTypeExtension
Ord, ReadPrec [ScalarTypeExtension]
ReadPrec ScalarTypeExtension
Int -> ReadS ScalarTypeExtension
ReadS [ScalarTypeExtension]
(Int -> ReadS ScalarTypeExtension)
-> ReadS [ScalarTypeExtension]
-> ReadPrec ScalarTypeExtension
-> ReadPrec [ScalarTypeExtension]
-> Read ScalarTypeExtension
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ScalarTypeExtension
readsPrec :: Int -> ReadS ScalarTypeExtension
$creadList :: ReadS [ScalarTypeExtension]
readList :: ReadS [ScalarTypeExtension]
$creadPrec :: ReadPrec ScalarTypeExtension
readPrec :: ReadPrec ScalarTypeExtension
$creadListPrec :: ReadPrec [ScalarTypeExtension]
readListPrec :: ReadPrec [ScalarTypeExtension]
Read, Int -> ScalarTypeExtension -> String -> String
[ScalarTypeExtension] -> String -> String
ScalarTypeExtension -> String
(Int -> ScalarTypeExtension -> String -> String)
-> (ScalarTypeExtension -> String)
-> ([ScalarTypeExtension] -> String -> String)
-> Show ScalarTypeExtension
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ScalarTypeExtension -> String -> String
showsPrec :: Int -> ScalarTypeExtension -> String -> String
$cshow :: ScalarTypeExtension -> String
show :: ScalarTypeExtension -> String
$cshowList :: [ScalarTypeExtension] -> String -> String
showList :: [ScalarTypeExtension] -> String -> String
Show)
_ScalarTypeExtension :: Name
_ScalarTypeExtension = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ScalarTypeExtension")
_ScalarTypeExtension_name :: Name
_ScalarTypeExtension_name = (String -> Name
Core.Name String
"name")
_ScalarTypeExtension_directives :: Name
_ScalarTypeExtension_directives = (String -> Name
Core.Name String
"directives")
data ObjectTypeDefinition =
ObjectTypeDefinition {
ObjectTypeDefinition -> Maybe Description
objectTypeDefinitionDescription :: (Maybe Description),
ObjectTypeDefinition -> Name
objectTypeDefinitionName :: Name,
ObjectTypeDefinition -> Maybe ImplementsInterfaces
objectTypeDefinitionImplementsInterfaces :: (Maybe ImplementsInterfaces),
ObjectTypeDefinition -> Maybe Directives
objectTypeDefinitionDirectives :: (Maybe Directives),
ObjectTypeDefinition -> Maybe FieldsDefinition
objectTypeDefinitionFieldsDefinition :: (Maybe FieldsDefinition)}
deriving (ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
(ObjectTypeDefinition -> ObjectTypeDefinition -> Bool)
-> (ObjectTypeDefinition -> ObjectTypeDefinition -> Bool)
-> Eq ObjectTypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
== :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
$c/= :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
/= :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
Eq, Eq ObjectTypeDefinition
Eq ObjectTypeDefinition =>
(ObjectTypeDefinition -> ObjectTypeDefinition -> Ordering)
-> (ObjectTypeDefinition -> ObjectTypeDefinition -> Bool)
-> (ObjectTypeDefinition -> ObjectTypeDefinition -> Bool)
-> (ObjectTypeDefinition -> ObjectTypeDefinition -> Bool)
-> (ObjectTypeDefinition -> ObjectTypeDefinition -> Bool)
-> (ObjectTypeDefinition
-> ObjectTypeDefinition -> ObjectTypeDefinition)
-> (ObjectTypeDefinition
-> ObjectTypeDefinition -> ObjectTypeDefinition)
-> Ord 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
$ccompare :: ObjectTypeDefinition -> ObjectTypeDefinition -> Ordering
compare :: ObjectTypeDefinition -> ObjectTypeDefinition -> Ordering
$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
>= :: ObjectTypeDefinition -> ObjectTypeDefinition -> Bool
$cmax :: ObjectTypeDefinition
-> ObjectTypeDefinition -> ObjectTypeDefinition
max :: ObjectTypeDefinition
-> ObjectTypeDefinition -> ObjectTypeDefinition
$cmin :: ObjectTypeDefinition
-> ObjectTypeDefinition -> ObjectTypeDefinition
min :: ObjectTypeDefinition
-> ObjectTypeDefinition -> ObjectTypeDefinition
Ord, ReadPrec [ObjectTypeDefinition]
ReadPrec ObjectTypeDefinition
Int -> ReadS ObjectTypeDefinition
ReadS [ObjectTypeDefinition]
(Int -> ReadS ObjectTypeDefinition)
-> ReadS [ObjectTypeDefinition]
-> ReadPrec ObjectTypeDefinition
-> ReadPrec [ObjectTypeDefinition]
-> Read ObjectTypeDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectTypeDefinition
readsPrec :: Int -> ReadS ObjectTypeDefinition
$creadList :: ReadS [ObjectTypeDefinition]
readList :: ReadS [ObjectTypeDefinition]
$creadPrec :: ReadPrec ObjectTypeDefinition
readPrec :: ReadPrec ObjectTypeDefinition
$creadListPrec :: ReadPrec [ObjectTypeDefinition]
readListPrec :: ReadPrec [ObjectTypeDefinition]
Read, Int -> ObjectTypeDefinition -> String -> String
[ObjectTypeDefinition] -> String -> String
ObjectTypeDefinition -> String
(Int -> ObjectTypeDefinition -> String -> String)
-> (ObjectTypeDefinition -> String)
-> ([ObjectTypeDefinition] -> String -> String)
-> Show ObjectTypeDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ObjectTypeDefinition -> String -> String
showsPrec :: Int -> ObjectTypeDefinition -> String -> String
$cshow :: ObjectTypeDefinition -> String
show :: ObjectTypeDefinition -> String
$cshowList :: [ObjectTypeDefinition] -> String -> String
showList :: [ObjectTypeDefinition] -> String -> String
Show)
_ObjectTypeDefinition :: Name
_ObjectTypeDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ObjectTypeDefinition")
_ObjectTypeDefinition_description :: Name
_ObjectTypeDefinition_description = (String -> Name
Core.Name String
"description")
_ObjectTypeDefinition_name :: Name
_ObjectTypeDefinition_name = (String -> Name
Core.Name String
"name")
_ObjectTypeDefinition_implementsInterfaces :: Name
_ObjectTypeDefinition_implementsInterfaces = (String -> Name
Core.Name String
"implementsInterfaces")
_ObjectTypeDefinition_directives :: Name
_ObjectTypeDefinition_directives = (String -> Name
Core.Name String
"directives")
_ObjectTypeDefinition_fieldsDefinition :: Name
_ObjectTypeDefinition_fieldsDefinition = (String -> Name
Core.Name String
"fieldsDefinition")
data ObjectTypeExtension =
ObjectTypeExtensionSequence ObjectTypeExtension_Sequence |
ObjectTypeExtensionSequence2 ObjectTypeExtension_Sequence2 |
ObjectTypeExtensionSequence3 ObjectTypeExtension_Sequence3
deriving (ObjectTypeExtension -> ObjectTypeExtension -> Bool
(ObjectTypeExtension -> ObjectTypeExtension -> Bool)
-> (ObjectTypeExtension -> ObjectTypeExtension -> Bool)
-> Eq ObjectTypeExtension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
== :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
$c/= :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
/= :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
Eq, Eq ObjectTypeExtension
Eq ObjectTypeExtension =>
(ObjectTypeExtension -> ObjectTypeExtension -> Ordering)
-> (ObjectTypeExtension -> ObjectTypeExtension -> Bool)
-> (ObjectTypeExtension -> ObjectTypeExtension -> Bool)
-> (ObjectTypeExtension -> ObjectTypeExtension -> Bool)
-> (ObjectTypeExtension -> ObjectTypeExtension -> Bool)
-> (ObjectTypeExtension
-> ObjectTypeExtension -> ObjectTypeExtension)
-> (ObjectTypeExtension
-> ObjectTypeExtension -> ObjectTypeExtension)
-> Ord 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
$ccompare :: ObjectTypeExtension -> ObjectTypeExtension -> Ordering
compare :: ObjectTypeExtension -> ObjectTypeExtension -> Ordering
$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
>= :: ObjectTypeExtension -> ObjectTypeExtension -> Bool
$cmax :: ObjectTypeExtension -> ObjectTypeExtension -> ObjectTypeExtension
max :: ObjectTypeExtension -> ObjectTypeExtension -> ObjectTypeExtension
$cmin :: ObjectTypeExtension -> ObjectTypeExtension -> ObjectTypeExtension
min :: ObjectTypeExtension -> ObjectTypeExtension -> ObjectTypeExtension
Ord, ReadPrec [ObjectTypeExtension]
ReadPrec ObjectTypeExtension
Int -> ReadS ObjectTypeExtension
ReadS [ObjectTypeExtension]
(Int -> ReadS ObjectTypeExtension)
-> ReadS [ObjectTypeExtension]
-> ReadPrec ObjectTypeExtension
-> ReadPrec [ObjectTypeExtension]
-> Read ObjectTypeExtension
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectTypeExtension
readsPrec :: Int -> ReadS ObjectTypeExtension
$creadList :: ReadS [ObjectTypeExtension]
readList :: ReadS [ObjectTypeExtension]
$creadPrec :: ReadPrec ObjectTypeExtension
readPrec :: ReadPrec ObjectTypeExtension
$creadListPrec :: ReadPrec [ObjectTypeExtension]
readListPrec :: ReadPrec [ObjectTypeExtension]
Read, Int -> ObjectTypeExtension -> String -> String
[ObjectTypeExtension] -> String -> String
ObjectTypeExtension -> String
(Int -> ObjectTypeExtension -> String -> String)
-> (ObjectTypeExtension -> String)
-> ([ObjectTypeExtension] -> String -> String)
-> Show ObjectTypeExtension
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ObjectTypeExtension -> String -> String
showsPrec :: Int -> ObjectTypeExtension -> String -> String
$cshow :: ObjectTypeExtension -> String
show :: ObjectTypeExtension -> String
$cshowList :: [ObjectTypeExtension] -> String -> String
showList :: [ObjectTypeExtension] -> String -> String
Show)
_ObjectTypeExtension :: Name
_ObjectTypeExtension = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ObjectTypeExtension")
_ObjectTypeExtension_sequence :: Name
_ObjectTypeExtension_sequence = (String -> Name
Core.Name String
"sequence")
_ObjectTypeExtension_sequence2 :: Name
_ObjectTypeExtension_sequence2 = (String -> Name
Core.Name String
"sequence2")
_ObjectTypeExtension_sequence3 :: Name
_ObjectTypeExtension_sequence3 = (String -> Name
Core.Name 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
(ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool)
-> (ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool)
-> Eq ObjectTypeExtension_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
== :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
$c/= :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
/= :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
Eq, Eq ObjectTypeExtension_Sequence
Eq ObjectTypeExtension_Sequence =>
(ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Ordering)
-> (ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool)
-> (ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool)
-> (ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool)
-> (ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool)
-> (ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> ObjectTypeExtension_Sequence)
-> (ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> ObjectTypeExtension_Sequence)
-> Ord 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
$ccompare :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Ordering
compare :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Ordering
$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
>= :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> Bool
$cmax :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> ObjectTypeExtension_Sequence
max :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> ObjectTypeExtension_Sequence
$cmin :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> ObjectTypeExtension_Sequence
min :: ObjectTypeExtension_Sequence
-> ObjectTypeExtension_Sequence -> ObjectTypeExtension_Sequence
Ord, ReadPrec [ObjectTypeExtension_Sequence]
ReadPrec ObjectTypeExtension_Sequence
Int -> ReadS ObjectTypeExtension_Sequence
ReadS [ObjectTypeExtension_Sequence]
(Int -> ReadS ObjectTypeExtension_Sequence)
-> ReadS [ObjectTypeExtension_Sequence]
-> ReadPrec ObjectTypeExtension_Sequence
-> ReadPrec [ObjectTypeExtension_Sequence]
-> Read ObjectTypeExtension_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectTypeExtension_Sequence
readsPrec :: Int -> ReadS ObjectTypeExtension_Sequence
$creadList :: ReadS [ObjectTypeExtension_Sequence]
readList :: ReadS [ObjectTypeExtension_Sequence]
$creadPrec :: ReadPrec ObjectTypeExtension_Sequence
readPrec :: ReadPrec ObjectTypeExtension_Sequence
$creadListPrec :: ReadPrec [ObjectTypeExtension_Sequence]
readListPrec :: ReadPrec [ObjectTypeExtension_Sequence]
Read, Int -> ObjectTypeExtension_Sequence -> String -> String
[ObjectTypeExtension_Sequence] -> String -> String
ObjectTypeExtension_Sequence -> String
(Int -> ObjectTypeExtension_Sequence -> String -> String)
-> (ObjectTypeExtension_Sequence -> String)
-> ([ObjectTypeExtension_Sequence] -> String -> String)
-> Show ObjectTypeExtension_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ObjectTypeExtension_Sequence -> String -> String
showsPrec :: Int -> ObjectTypeExtension_Sequence -> String -> String
$cshow :: ObjectTypeExtension_Sequence -> String
show :: ObjectTypeExtension_Sequence -> String
$cshowList :: [ObjectTypeExtension_Sequence] -> String -> String
showList :: [ObjectTypeExtension_Sequence] -> String -> String
Show)
_ObjectTypeExtension_Sequence :: Name
_ObjectTypeExtension_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ObjectTypeExtension.Sequence")
_ObjectTypeExtension_Sequence_name :: Name
_ObjectTypeExtension_Sequence_name = (String -> Name
Core.Name String
"name")
_ObjectTypeExtension_Sequence_implementsInterfaces :: Name
_ObjectTypeExtension_Sequence_implementsInterfaces = (String -> Name
Core.Name String
"implementsInterfaces")
_ObjectTypeExtension_Sequence_directives :: Name
_ObjectTypeExtension_Sequence_directives = (String -> Name
Core.Name String
"directives")
_ObjectTypeExtension_Sequence_fieldsDefinition :: Name
_ObjectTypeExtension_Sequence_fieldsDefinition = (String -> Name
Core.Name 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
(ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool)
-> (ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool)
-> Eq ObjectTypeExtension_Sequence2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
== :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
$c/= :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
/= :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
Eq, Eq ObjectTypeExtension_Sequence2
Eq ObjectTypeExtension_Sequence2 =>
(ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Ordering)
-> (ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool)
-> (ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool)
-> (ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool)
-> (ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool)
-> (ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> ObjectTypeExtension_Sequence2)
-> (ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> ObjectTypeExtension_Sequence2)
-> Ord 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
$ccompare :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Ordering
compare :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Ordering
$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
>= :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> Bool
$cmax :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> ObjectTypeExtension_Sequence2
max :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> ObjectTypeExtension_Sequence2
$cmin :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> ObjectTypeExtension_Sequence2
min :: ObjectTypeExtension_Sequence2
-> ObjectTypeExtension_Sequence2 -> ObjectTypeExtension_Sequence2
Ord, ReadPrec [ObjectTypeExtension_Sequence2]
ReadPrec ObjectTypeExtension_Sequence2
Int -> ReadS ObjectTypeExtension_Sequence2
ReadS [ObjectTypeExtension_Sequence2]
(Int -> ReadS ObjectTypeExtension_Sequence2)
-> ReadS [ObjectTypeExtension_Sequence2]
-> ReadPrec ObjectTypeExtension_Sequence2
-> ReadPrec [ObjectTypeExtension_Sequence2]
-> Read ObjectTypeExtension_Sequence2
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectTypeExtension_Sequence2
readsPrec :: Int -> ReadS ObjectTypeExtension_Sequence2
$creadList :: ReadS [ObjectTypeExtension_Sequence2]
readList :: ReadS [ObjectTypeExtension_Sequence2]
$creadPrec :: ReadPrec ObjectTypeExtension_Sequence2
readPrec :: ReadPrec ObjectTypeExtension_Sequence2
$creadListPrec :: ReadPrec [ObjectTypeExtension_Sequence2]
readListPrec :: ReadPrec [ObjectTypeExtension_Sequence2]
Read, Int -> ObjectTypeExtension_Sequence2 -> String -> String
[ObjectTypeExtension_Sequence2] -> String -> String
ObjectTypeExtension_Sequence2 -> String
(Int -> ObjectTypeExtension_Sequence2 -> String -> String)
-> (ObjectTypeExtension_Sequence2 -> String)
-> ([ObjectTypeExtension_Sequence2] -> String -> String)
-> Show ObjectTypeExtension_Sequence2
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ObjectTypeExtension_Sequence2 -> String -> String
showsPrec :: Int -> ObjectTypeExtension_Sequence2 -> String -> String
$cshow :: ObjectTypeExtension_Sequence2 -> String
show :: ObjectTypeExtension_Sequence2 -> String
$cshowList :: [ObjectTypeExtension_Sequence2] -> String -> String
showList :: [ObjectTypeExtension_Sequence2] -> String -> String
Show)
_ObjectTypeExtension_Sequence2 :: Name
_ObjectTypeExtension_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ObjectTypeExtension.Sequence2")
_ObjectTypeExtension_Sequence2_name :: Name
_ObjectTypeExtension_Sequence2_name = (String -> Name
Core.Name String
"name")
_ObjectTypeExtension_Sequence2_implementsInterfaces :: Name
_ObjectTypeExtension_Sequence2_implementsInterfaces = (String -> Name
Core.Name String
"implementsInterfaces")
_ObjectTypeExtension_Sequence2_directives :: Name
_ObjectTypeExtension_Sequence2_directives = (String -> Name
Core.Name 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
(ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool)
-> (ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool)
-> Eq ObjectTypeExtension_Sequence3
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
== :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
$c/= :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
/= :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
Eq, Eq ObjectTypeExtension_Sequence3
Eq ObjectTypeExtension_Sequence3 =>
(ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Ordering)
-> (ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool)
-> (ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool)
-> (ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool)
-> (ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool)
-> (ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> ObjectTypeExtension_Sequence3)
-> (ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> ObjectTypeExtension_Sequence3)
-> Ord 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
$ccompare :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Ordering
compare :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Ordering
$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
>= :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> Bool
$cmax :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> ObjectTypeExtension_Sequence3
max :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> ObjectTypeExtension_Sequence3
$cmin :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> ObjectTypeExtension_Sequence3
min :: ObjectTypeExtension_Sequence3
-> ObjectTypeExtension_Sequence3 -> ObjectTypeExtension_Sequence3
Ord, ReadPrec [ObjectTypeExtension_Sequence3]
ReadPrec ObjectTypeExtension_Sequence3
Int -> ReadS ObjectTypeExtension_Sequence3
ReadS [ObjectTypeExtension_Sequence3]
(Int -> ReadS ObjectTypeExtension_Sequence3)
-> ReadS [ObjectTypeExtension_Sequence3]
-> ReadPrec ObjectTypeExtension_Sequence3
-> ReadPrec [ObjectTypeExtension_Sequence3]
-> Read ObjectTypeExtension_Sequence3
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ObjectTypeExtension_Sequence3
readsPrec :: Int -> ReadS ObjectTypeExtension_Sequence3
$creadList :: ReadS [ObjectTypeExtension_Sequence3]
readList :: ReadS [ObjectTypeExtension_Sequence3]
$creadPrec :: ReadPrec ObjectTypeExtension_Sequence3
readPrec :: ReadPrec ObjectTypeExtension_Sequence3
$creadListPrec :: ReadPrec [ObjectTypeExtension_Sequence3]
readListPrec :: ReadPrec [ObjectTypeExtension_Sequence3]
Read, Int -> ObjectTypeExtension_Sequence3 -> String -> String
[ObjectTypeExtension_Sequence3] -> String -> String
ObjectTypeExtension_Sequence3 -> String
(Int -> ObjectTypeExtension_Sequence3 -> String -> String)
-> (ObjectTypeExtension_Sequence3 -> String)
-> ([ObjectTypeExtension_Sequence3] -> String -> String)
-> Show ObjectTypeExtension_Sequence3
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ObjectTypeExtension_Sequence3 -> String -> String
showsPrec :: Int -> ObjectTypeExtension_Sequence3 -> String -> String
$cshow :: ObjectTypeExtension_Sequence3 -> String
show :: ObjectTypeExtension_Sequence3 -> String
$cshowList :: [ObjectTypeExtension_Sequence3] -> String -> String
showList :: [ObjectTypeExtension_Sequence3] -> String -> String
Show)
_ObjectTypeExtension_Sequence3 :: Name
_ObjectTypeExtension_Sequence3 = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ObjectTypeExtension.Sequence3")
_ObjectTypeExtension_Sequence3_name :: Name
_ObjectTypeExtension_Sequence3_name = (String -> Name
Core.Name String
"name")
_ObjectTypeExtension_Sequence3_implementsInterfaces :: Name
_ObjectTypeExtension_Sequence3_implementsInterfaces = (String -> Name
Core.Name String
"implementsInterfaces")
data ImplementsInterfaces =
ImplementsInterfacesSequence ImplementsInterfaces_Sequence |
ImplementsInterfacesSequence2 ImplementsInterfaces_Sequence2
deriving (ImplementsInterfaces -> ImplementsInterfaces -> Bool
(ImplementsInterfaces -> ImplementsInterfaces -> Bool)
-> (ImplementsInterfaces -> ImplementsInterfaces -> Bool)
-> Eq ImplementsInterfaces
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
== :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
$c/= :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
/= :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
Eq, Eq ImplementsInterfaces
Eq ImplementsInterfaces =>
(ImplementsInterfaces -> ImplementsInterfaces -> Ordering)
-> (ImplementsInterfaces -> ImplementsInterfaces -> Bool)
-> (ImplementsInterfaces -> ImplementsInterfaces -> Bool)
-> (ImplementsInterfaces -> ImplementsInterfaces -> Bool)
-> (ImplementsInterfaces -> ImplementsInterfaces -> Bool)
-> (ImplementsInterfaces
-> ImplementsInterfaces -> ImplementsInterfaces)
-> (ImplementsInterfaces
-> ImplementsInterfaces -> ImplementsInterfaces)
-> Ord 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
$ccompare :: ImplementsInterfaces -> ImplementsInterfaces -> Ordering
compare :: ImplementsInterfaces -> ImplementsInterfaces -> Ordering
$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
>= :: ImplementsInterfaces -> ImplementsInterfaces -> Bool
$cmax :: ImplementsInterfaces
-> ImplementsInterfaces -> ImplementsInterfaces
max :: ImplementsInterfaces
-> ImplementsInterfaces -> ImplementsInterfaces
$cmin :: ImplementsInterfaces
-> ImplementsInterfaces -> ImplementsInterfaces
min :: ImplementsInterfaces
-> ImplementsInterfaces -> ImplementsInterfaces
Ord, ReadPrec [ImplementsInterfaces]
ReadPrec ImplementsInterfaces
Int -> ReadS ImplementsInterfaces
ReadS [ImplementsInterfaces]
(Int -> ReadS ImplementsInterfaces)
-> ReadS [ImplementsInterfaces]
-> ReadPrec ImplementsInterfaces
-> ReadPrec [ImplementsInterfaces]
-> Read ImplementsInterfaces
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ImplementsInterfaces
readsPrec :: Int -> ReadS ImplementsInterfaces
$creadList :: ReadS [ImplementsInterfaces]
readList :: ReadS [ImplementsInterfaces]
$creadPrec :: ReadPrec ImplementsInterfaces
readPrec :: ReadPrec ImplementsInterfaces
$creadListPrec :: ReadPrec [ImplementsInterfaces]
readListPrec :: ReadPrec [ImplementsInterfaces]
Read, Int -> ImplementsInterfaces -> String -> String
[ImplementsInterfaces] -> String -> String
ImplementsInterfaces -> String
(Int -> ImplementsInterfaces -> String -> String)
-> (ImplementsInterfaces -> String)
-> ([ImplementsInterfaces] -> String -> String)
-> Show ImplementsInterfaces
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ImplementsInterfaces -> String -> String
showsPrec :: Int -> ImplementsInterfaces -> String -> String
$cshow :: ImplementsInterfaces -> String
show :: ImplementsInterfaces -> String
$cshowList :: [ImplementsInterfaces] -> String -> String
showList :: [ImplementsInterfaces] -> String -> String
Show)
_ImplementsInterfaces :: Name
_ImplementsInterfaces = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ImplementsInterfaces")
_ImplementsInterfaces_sequence :: Name
_ImplementsInterfaces_sequence = (String -> Name
Core.Name String
"sequence")
_ImplementsInterfaces_sequence2 :: Name
_ImplementsInterfaces_sequence2 = (String -> Name
Core.Name 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
(ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool)
-> (ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool)
-> Eq ImplementsInterfaces_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
== :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
$c/= :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
/= :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
Eq, Eq ImplementsInterfaces_Sequence
Eq ImplementsInterfaces_Sequence =>
(ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Ordering)
-> (ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool)
-> (ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool)
-> (ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool)
-> (ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool)
-> (ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> ImplementsInterfaces_Sequence)
-> (ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> ImplementsInterfaces_Sequence)
-> Ord 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
$ccompare :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Ordering
compare :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Ordering
$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
>= :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> Bool
$cmax :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> ImplementsInterfaces_Sequence
max :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> ImplementsInterfaces_Sequence
$cmin :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> ImplementsInterfaces_Sequence
min :: ImplementsInterfaces_Sequence
-> ImplementsInterfaces_Sequence -> ImplementsInterfaces_Sequence
Ord, ReadPrec [ImplementsInterfaces_Sequence]
ReadPrec ImplementsInterfaces_Sequence
Int -> ReadS ImplementsInterfaces_Sequence
ReadS [ImplementsInterfaces_Sequence]
(Int -> ReadS ImplementsInterfaces_Sequence)
-> ReadS [ImplementsInterfaces_Sequence]
-> ReadPrec ImplementsInterfaces_Sequence
-> ReadPrec [ImplementsInterfaces_Sequence]
-> Read ImplementsInterfaces_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ImplementsInterfaces_Sequence
readsPrec :: Int -> ReadS ImplementsInterfaces_Sequence
$creadList :: ReadS [ImplementsInterfaces_Sequence]
readList :: ReadS [ImplementsInterfaces_Sequence]
$creadPrec :: ReadPrec ImplementsInterfaces_Sequence
readPrec :: ReadPrec ImplementsInterfaces_Sequence
$creadListPrec :: ReadPrec [ImplementsInterfaces_Sequence]
readListPrec :: ReadPrec [ImplementsInterfaces_Sequence]
Read, Int -> ImplementsInterfaces_Sequence -> String -> String
[ImplementsInterfaces_Sequence] -> String -> String
ImplementsInterfaces_Sequence -> String
(Int -> ImplementsInterfaces_Sequence -> String -> String)
-> (ImplementsInterfaces_Sequence -> String)
-> ([ImplementsInterfaces_Sequence] -> String -> String)
-> Show ImplementsInterfaces_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ImplementsInterfaces_Sequence -> String -> String
showsPrec :: Int -> ImplementsInterfaces_Sequence -> String -> String
$cshow :: ImplementsInterfaces_Sequence -> String
show :: ImplementsInterfaces_Sequence -> String
$cshowList :: [ImplementsInterfaces_Sequence] -> String -> String
showList :: [ImplementsInterfaces_Sequence] -> String -> String
Show)
_ImplementsInterfaces_Sequence :: Name
_ImplementsInterfaces_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ImplementsInterfaces.Sequence")
_ImplementsInterfaces_Sequence_implementsInterfaces :: Name
_ImplementsInterfaces_Sequence_implementsInterfaces = (String -> Name
Core.Name String
"implementsInterfaces")
_ImplementsInterfaces_Sequence_namedType :: Name
_ImplementsInterfaces_Sequence_namedType = (String -> Name
Core.Name 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
(ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool)
-> (ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool)
-> Eq ImplementsInterfaces_Sequence2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
== :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
$c/= :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
/= :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
Eq, Eq ImplementsInterfaces_Sequence2
Eq ImplementsInterfaces_Sequence2 =>
(ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Ordering)
-> (ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool)
-> (ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool)
-> (ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool)
-> (ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool)
-> (ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2)
-> (ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2)
-> Ord 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
$ccompare :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Ordering
compare :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Ordering
$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
>= :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> Bool
$cmax :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> ImplementsInterfaces_Sequence2
max :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> ImplementsInterfaces_Sequence2
$cmin :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> ImplementsInterfaces_Sequence2
min :: ImplementsInterfaces_Sequence2
-> ImplementsInterfaces_Sequence2 -> ImplementsInterfaces_Sequence2
Ord, ReadPrec [ImplementsInterfaces_Sequence2]
ReadPrec ImplementsInterfaces_Sequence2
Int -> ReadS ImplementsInterfaces_Sequence2
ReadS [ImplementsInterfaces_Sequence2]
(Int -> ReadS ImplementsInterfaces_Sequence2)
-> ReadS [ImplementsInterfaces_Sequence2]
-> ReadPrec ImplementsInterfaces_Sequence2
-> ReadPrec [ImplementsInterfaces_Sequence2]
-> Read ImplementsInterfaces_Sequence2
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ImplementsInterfaces_Sequence2
readsPrec :: Int -> ReadS ImplementsInterfaces_Sequence2
$creadList :: ReadS [ImplementsInterfaces_Sequence2]
readList :: ReadS [ImplementsInterfaces_Sequence2]
$creadPrec :: ReadPrec ImplementsInterfaces_Sequence2
readPrec :: ReadPrec ImplementsInterfaces_Sequence2
$creadListPrec :: ReadPrec [ImplementsInterfaces_Sequence2]
readListPrec :: ReadPrec [ImplementsInterfaces_Sequence2]
Read, Int -> ImplementsInterfaces_Sequence2 -> String -> String
[ImplementsInterfaces_Sequence2] -> String -> String
ImplementsInterfaces_Sequence2 -> String
(Int -> ImplementsInterfaces_Sequence2 -> String -> String)
-> (ImplementsInterfaces_Sequence2 -> String)
-> ([ImplementsInterfaces_Sequence2] -> String -> String)
-> Show ImplementsInterfaces_Sequence2
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ImplementsInterfaces_Sequence2 -> String -> String
showsPrec :: Int -> ImplementsInterfaces_Sequence2 -> String -> String
$cshow :: ImplementsInterfaces_Sequence2 -> String
show :: ImplementsInterfaces_Sequence2 -> String
$cshowList :: [ImplementsInterfaces_Sequence2] -> String -> String
showList :: [ImplementsInterfaces_Sequence2] -> String -> String
Show)
_ImplementsInterfaces_Sequence2 :: Name
_ImplementsInterfaces_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ImplementsInterfaces.Sequence2")
_ImplementsInterfaces_Sequence2_amp :: Name
_ImplementsInterfaces_Sequence2_amp = (String -> Name
Core.Name String
"amp")
_ImplementsInterfaces_Sequence2_namedType :: Name
_ImplementsInterfaces_Sequence2_namedType = (String -> Name
Core.Name String
"namedType")
newtype FieldsDefinition =
FieldsDefinition {
FieldsDefinition -> [FieldDefinition]
unFieldsDefinition :: [FieldDefinition]}
deriving (FieldsDefinition -> FieldsDefinition -> Bool
(FieldsDefinition -> FieldsDefinition -> Bool)
-> (FieldsDefinition -> FieldsDefinition -> Bool)
-> Eq FieldsDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldsDefinition -> FieldsDefinition -> Bool
== :: FieldsDefinition -> FieldsDefinition -> Bool
$c/= :: FieldsDefinition -> FieldsDefinition -> Bool
/= :: FieldsDefinition -> FieldsDefinition -> Bool
Eq, Eq FieldsDefinition
Eq FieldsDefinition =>
(FieldsDefinition -> FieldsDefinition -> Ordering)
-> (FieldsDefinition -> FieldsDefinition -> Bool)
-> (FieldsDefinition -> FieldsDefinition -> Bool)
-> (FieldsDefinition -> FieldsDefinition -> Bool)
-> (FieldsDefinition -> FieldsDefinition -> Bool)
-> (FieldsDefinition -> FieldsDefinition -> FieldsDefinition)
-> (FieldsDefinition -> FieldsDefinition -> FieldsDefinition)
-> Ord 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
$ccompare :: FieldsDefinition -> FieldsDefinition -> Ordering
compare :: FieldsDefinition -> FieldsDefinition -> Ordering
$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
>= :: FieldsDefinition -> FieldsDefinition -> Bool
$cmax :: FieldsDefinition -> FieldsDefinition -> FieldsDefinition
max :: FieldsDefinition -> FieldsDefinition -> FieldsDefinition
$cmin :: FieldsDefinition -> FieldsDefinition -> FieldsDefinition
min :: FieldsDefinition -> FieldsDefinition -> FieldsDefinition
Ord, ReadPrec [FieldsDefinition]
ReadPrec FieldsDefinition
Int -> ReadS FieldsDefinition
ReadS [FieldsDefinition]
(Int -> ReadS FieldsDefinition)
-> ReadS [FieldsDefinition]
-> ReadPrec FieldsDefinition
-> ReadPrec [FieldsDefinition]
-> Read FieldsDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FieldsDefinition
readsPrec :: Int -> ReadS FieldsDefinition
$creadList :: ReadS [FieldsDefinition]
readList :: ReadS [FieldsDefinition]
$creadPrec :: ReadPrec FieldsDefinition
readPrec :: ReadPrec FieldsDefinition
$creadListPrec :: ReadPrec [FieldsDefinition]
readListPrec :: ReadPrec [FieldsDefinition]
Read, Int -> FieldsDefinition -> String -> String
[FieldsDefinition] -> String -> String
FieldsDefinition -> String
(Int -> FieldsDefinition -> String -> String)
-> (FieldsDefinition -> String)
-> ([FieldsDefinition] -> String -> String)
-> Show FieldsDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> FieldsDefinition -> String -> String
showsPrec :: Int -> FieldsDefinition -> String -> String
$cshow :: FieldsDefinition -> String
show :: FieldsDefinition -> String
$cshowList :: [FieldsDefinition] -> String -> String
showList :: [FieldsDefinition] -> String -> String
Show)
_FieldsDefinition :: Name
_FieldsDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.FieldsDefinition")
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
(FieldDefinition -> FieldDefinition -> Bool)
-> (FieldDefinition -> FieldDefinition -> Bool)
-> Eq FieldDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FieldDefinition -> FieldDefinition -> Bool
== :: FieldDefinition -> FieldDefinition -> Bool
$c/= :: FieldDefinition -> FieldDefinition -> Bool
/= :: FieldDefinition -> FieldDefinition -> Bool
Eq, Eq FieldDefinition
Eq FieldDefinition =>
(FieldDefinition -> FieldDefinition -> Ordering)
-> (FieldDefinition -> FieldDefinition -> Bool)
-> (FieldDefinition -> FieldDefinition -> Bool)
-> (FieldDefinition -> FieldDefinition -> Bool)
-> (FieldDefinition -> FieldDefinition -> Bool)
-> (FieldDefinition -> FieldDefinition -> FieldDefinition)
-> (FieldDefinition -> FieldDefinition -> FieldDefinition)
-> Ord 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
$ccompare :: FieldDefinition -> FieldDefinition -> Ordering
compare :: FieldDefinition -> FieldDefinition -> Ordering
$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
>= :: FieldDefinition -> FieldDefinition -> Bool
$cmax :: FieldDefinition -> FieldDefinition -> FieldDefinition
max :: FieldDefinition -> FieldDefinition -> FieldDefinition
$cmin :: FieldDefinition -> FieldDefinition -> FieldDefinition
min :: FieldDefinition -> FieldDefinition -> FieldDefinition
Ord, ReadPrec [FieldDefinition]
ReadPrec FieldDefinition
Int -> ReadS FieldDefinition
ReadS [FieldDefinition]
(Int -> ReadS FieldDefinition)
-> ReadS [FieldDefinition]
-> ReadPrec FieldDefinition
-> ReadPrec [FieldDefinition]
-> Read FieldDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS FieldDefinition
readsPrec :: Int -> ReadS FieldDefinition
$creadList :: ReadS [FieldDefinition]
readList :: ReadS [FieldDefinition]
$creadPrec :: ReadPrec FieldDefinition
readPrec :: ReadPrec FieldDefinition
$creadListPrec :: ReadPrec [FieldDefinition]
readListPrec :: ReadPrec [FieldDefinition]
Read, Int -> FieldDefinition -> String -> String
[FieldDefinition] -> String -> String
FieldDefinition -> String
(Int -> FieldDefinition -> String -> String)
-> (FieldDefinition -> String)
-> ([FieldDefinition] -> String -> String)
-> Show FieldDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> FieldDefinition -> String -> String
showsPrec :: Int -> FieldDefinition -> String -> String
$cshow :: FieldDefinition -> String
show :: FieldDefinition -> String
$cshowList :: [FieldDefinition] -> String -> String
showList :: [FieldDefinition] -> String -> String
Show)
_FieldDefinition :: Name
_FieldDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.FieldDefinition")
_FieldDefinition_description :: Name
_FieldDefinition_description = (String -> Name
Core.Name String
"description")
_FieldDefinition_name :: Name
_FieldDefinition_name = (String -> Name
Core.Name String
"name")
_FieldDefinition_argumentsDefinition :: Name
_FieldDefinition_argumentsDefinition = (String -> Name
Core.Name String
"argumentsDefinition")
_FieldDefinition_type :: Name
_FieldDefinition_type = (String -> Name
Core.Name String
"type")
_FieldDefinition_directives :: Name
_FieldDefinition_directives = (String -> Name
Core.Name String
"directives")
newtype ArgumentsDefinition =
ArgumentsDefinition {
ArgumentsDefinition -> [InputValueDefinition]
unArgumentsDefinition :: [InputValueDefinition]}
deriving (ArgumentsDefinition -> ArgumentsDefinition -> Bool
(ArgumentsDefinition -> ArgumentsDefinition -> Bool)
-> (ArgumentsDefinition -> ArgumentsDefinition -> Bool)
-> Eq ArgumentsDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
== :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
$c/= :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
/= :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
Eq, Eq ArgumentsDefinition
Eq ArgumentsDefinition =>
(ArgumentsDefinition -> ArgumentsDefinition -> Ordering)
-> (ArgumentsDefinition -> ArgumentsDefinition -> Bool)
-> (ArgumentsDefinition -> ArgumentsDefinition -> Bool)
-> (ArgumentsDefinition -> ArgumentsDefinition -> Bool)
-> (ArgumentsDefinition -> ArgumentsDefinition -> Bool)
-> (ArgumentsDefinition
-> ArgumentsDefinition -> ArgumentsDefinition)
-> (ArgumentsDefinition
-> ArgumentsDefinition -> ArgumentsDefinition)
-> Ord 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
$ccompare :: ArgumentsDefinition -> ArgumentsDefinition -> Ordering
compare :: ArgumentsDefinition -> ArgumentsDefinition -> Ordering
$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
>= :: ArgumentsDefinition -> ArgumentsDefinition -> Bool
$cmax :: ArgumentsDefinition -> ArgumentsDefinition -> ArgumentsDefinition
max :: ArgumentsDefinition -> ArgumentsDefinition -> ArgumentsDefinition
$cmin :: ArgumentsDefinition -> ArgumentsDefinition -> ArgumentsDefinition
min :: ArgumentsDefinition -> ArgumentsDefinition -> ArgumentsDefinition
Ord, ReadPrec [ArgumentsDefinition]
ReadPrec ArgumentsDefinition
Int -> ReadS ArgumentsDefinition
ReadS [ArgumentsDefinition]
(Int -> ReadS ArgumentsDefinition)
-> ReadS [ArgumentsDefinition]
-> ReadPrec ArgumentsDefinition
-> ReadPrec [ArgumentsDefinition]
-> Read ArgumentsDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ArgumentsDefinition
readsPrec :: Int -> ReadS ArgumentsDefinition
$creadList :: ReadS [ArgumentsDefinition]
readList :: ReadS [ArgumentsDefinition]
$creadPrec :: ReadPrec ArgumentsDefinition
readPrec :: ReadPrec ArgumentsDefinition
$creadListPrec :: ReadPrec [ArgumentsDefinition]
readListPrec :: ReadPrec [ArgumentsDefinition]
Read, Int -> ArgumentsDefinition -> String -> String
[ArgumentsDefinition] -> String -> String
ArgumentsDefinition -> String
(Int -> ArgumentsDefinition -> String -> String)
-> (ArgumentsDefinition -> String)
-> ([ArgumentsDefinition] -> String -> String)
-> Show ArgumentsDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ArgumentsDefinition -> String -> String
showsPrec :: Int -> ArgumentsDefinition -> String -> String
$cshow :: ArgumentsDefinition -> String
show :: ArgumentsDefinition -> String
$cshowList :: [ArgumentsDefinition] -> String -> String
showList :: [ArgumentsDefinition] -> String -> String
Show)
_ArgumentsDefinition :: Name
_ArgumentsDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ArgumentsDefinition")
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
(InputValueDefinition -> InputValueDefinition -> Bool)
-> (InputValueDefinition -> InputValueDefinition -> Bool)
-> Eq InputValueDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InputValueDefinition -> InputValueDefinition -> Bool
== :: InputValueDefinition -> InputValueDefinition -> Bool
$c/= :: InputValueDefinition -> InputValueDefinition -> Bool
/= :: InputValueDefinition -> InputValueDefinition -> Bool
Eq, Eq InputValueDefinition
Eq InputValueDefinition =>
(InputValueDefinition -> InputValueDefinition -> Ordering)
-> (InputValueDefinition -> InputValueDefinition -> Bool)
-> (InputValueDefinition -> InputValueDefinition -> Bool)
-> (InputValueDefinition -> InputValueDefinition -> Bool)
-> (InputValueDefinition -> InputValueDefinition -> Bool)
-> (InputValueDefinition
-> InputValueDefinition -> InputValueDefinition)
-> (InputValueDefinition
-> InputValueDefinition -> InputValueDefinition)
-> Ord 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
$ccompare :: InputValueDefinition -> InputValueDefinition -> Ordering
compare :: InputValueDefinition -> InputValueDefinition -> Ordering
$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
>= :: InputValueDefinition -> InputValueDefinition -> Bool
$cmax :: InputValueDefinition
-> InputValueDefinition -> InputValueDefinition
max :: InputValueDefinition
-> InputValueDefinition -> InputValueDefinition
$cmin :: InputValueDefinition
-> InputValueDefinition -> InputValueDefinition
min :: InputValueDefinition
-> InputValueDefinition -> InputValueDefinition
Ord, ReadPrec [InputValueDefinition]
ReadPrec InputValueDefinition
Int -> ReadS InputValueDefinition
ReadS [InputValueDefinition]
(Int -> ReadS InputValueDefinition)
-> ReadS [InputValueDefinition]
-> ReadPrec InputValueDefinition
-> ReadPrec [InputValueDefinition]
-> Read InputValueDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InputValueDefinition
readsPrec :: Int -> ReadS InputValueDefinition
$creadList :: ReadS [InputValueDefinition]
readList :: ReadS [InputValueDefinition]
$creadPrec :: ReadPrec InputValueDefinition
readPrec :: ReadPrec InputValueDefinition
$creadListPrec :: ReadPrec [InputValueDefinition]
readListPrec :: ReadPrec [InputValueDefinition]
Read, Int -> InputValueDefinition -> String -> String
[InputValueDefinition] -> String -> String
InputValueDefinition -> String
(Int -> InputValueDefinition -> String -> String)
-> (InputValueDefinition -> String)
-> ([InputValueDefinition] -> String -> String)
-> Show InputValueDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InputValueDefinition -> String -> String
showsPrec :: Int -> InputValueDefinition -> String -> String
$cshow :: InputValueDefinition -> String
show :: InputValueDefinition -> String
$cshowList :: [InputValueDefinition] -> String -> String
showList :: [InputValueDefinition] -> String -> String
Show)
_InputValueDefinition :: Name
_InputValueDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InputValueDefinition")
_InputValueDefinition_description :: Name
_InputValueDefinition_description = (String -> Name
Core.Name String
"description")
_InputValueDefinition_name :: Name
_InputValueDefinition_name = (String -> Name
Core.Name String
"name")
_InputValueDefinition_type :: Name
_InputValueDefinition_type = (String -> Name
Core.Name String
"type")
_InputValueDefinition_defaultValue :: Name
_InputValueDefinition_defaultValue = (String -> Name
Core.Name String
"defaultValue")
_InputValueDefinition_directives :: Name
_InputValueDefinition_directives = (String -> Name
Core.Name String
"directives")
data InterfaceTypeDefinition =
InterfaceTypeDefinitionSequence InterfaceTypeDefinition_Sequence |
InterfaceTypeDefinitionSequence2 InterfaceTypeDefinition_Sequence2
deriving (InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
(InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool)
-> (InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool)
-> Eq InterfaceTypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
== :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
$c/= :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
/= :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
Eq, Eq InterfaceTypeDefinition
Eq InterfaceTypeDefinition =>
(InterfaceTypeDefinition -> InterfaceTypeDefinition -> Ordering)
-> (InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool)
-> (InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool)
-> (InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool)
-> (InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool)
-> (InterfaceTypeDefinition
-> InterfaceTypeDefinition -> InterfaceTypeDefinition)
-> (InterfaceTypeDefinition
-> InterfaceTypeDefinition -> InterfaceTypeDefinition)
-> Ord 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
$ccompare :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Ordering
compare :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Ordering
$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
>= :: InterfaceTypeDefinition -> InterfaceTypeDefinition -> Bool
$cmax :: InterfaceTypeDefinition
-> InterfaceTypeDefinition -> InterfaceTypeDefinition
max :: InterfaceTypeDefinition
-> InterfaceTypeDefinition -> InterfaceTypeDefinition
$cmin :: InterfaceTypeDefinition
-> InterfaceTypeDefinition -> InterfaceTypeDefinition
min :: InterfaceTypeDefinition
-> InterfaceTypeDefinition -> InterfaceTypeDefinition
Ord, ReadPrec [InterfaceTypeDefinition]
ReadPrec InterfaceTypeDefinition
Int -> ReadS InterfaceTypeDefinition
ReadS [InterfaceTypeDefinition]
(Int -> ReadS InterfaceTypeDefinition)
-> ReadS [InterfaceTypeDefinition]
-> ReadPrec InterfaceTypeDefinition
-> ReadPrec [InterfaceTypeDefinition]
-> Read InterfaceTypeDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InterfaceTypeDefinition
readsPrec :: Int -> ReadS InterfaceTypeDefinition
$creadList :: ReadS [InterfaceTypeDefinition]
readList :: ReadS [InterfaceTypeDefinition]
$creadPrec :: ReadPrec InterfaceTypeDefinition
readPrec :: ReadPrec InterfaceTypeDefinition
$creadListPrec :: ReadPrec [InterfaceTypeDefinition]
readListPrec :: ReadPrec [InterfaceTypeDefinition]
Read, Int -> InterfaceTypeDefinition -> String -> String
[InterfaceTypeDefinition] -> String -> String
InterfaceTypeDefinition -> String
(Int -> InterfaceTypeDefinition -> String -> String)
-> (InterfaceTypeDefinition -> String)
-> ([InterfaceTypeDefinition] -> String -> String)
-> Show InterfaceTypeDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InterfaceTypeDefinition -> String -> String
showsPrec :: Int -> InterfaceTypeDefinition -> String -> String
$cshow :: InterfaceTypeDefinition -> String
show :: InterfaceTypeDefinition -> String
$cshowList :: [InterfaceTypeDefinition] -> String -> String
showList :: [InterfaceTypeDefinition] -> String -> String
Show)
_InterfaceTypeDefinition :: Name
_InterfaceTypeDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InterfaceTypeDefinition")
_InterfaceTypeDefinition_sequence :: Name
_InterfaceTypeDefinition_sequence = (String -> Name
Core.Name String
"sequence")
_InterfaceTypeDefinition_sequence2 :: Name
_InterfaceTypeDefinition_sequence2 = (String -> Name
Core.Name 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
(InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool)
-> (InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool)
-> Eq InterfaceTypeDefinition_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
== :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
$c/= :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
/= :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
Eq, Eq InterfaceTypeDefinition_Sequence
Eq InterfaceTypeDefinition_Sequence =>
(InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Ordering)
-> (InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool)
-> (InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool)
-> (InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool)
-> (InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool)
-> (InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence)
-> (InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence)
-> Ord 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
$ccompare :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Ordering
compare :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Ordering
$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
>= :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence -> Bool
$cmax :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
max :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
$cmin :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
min :: InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
-> InterfaceTypeDefinition_Sequence
Ord, ReadPrec [InterfaceTypeDefinition_Sequence]
ReadPrec InterfaceTypeDefinition_Sequence
Int -> ReadS InterfaceTypeDefinition_Sequence
ReadS [InterfaceTypeDefinition_Sequence]
(Int -> ReadS InterfaceTypeDefinition_Sequence)
-> ReadS [InterfaceTypeDefinition_Sequence]
-> ReadPrec InterfaceTypeDefinition_Sequence
-> ReadPrec [InterfaceTypeDefinition_Sequence]
-> Read InterfaceTypeDefinition_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InterfaceTypeDefinition_Sequence
readsPrec :: Int -> ReadS InterfaceTypeDefinition_Sequence
$creadList :: ReadS [InterfaceTypeDefinition_Sequence]
readList :: ReadS [InterfaceTypeDefinition_Sequence]
$creadPrec :: ReadPrec InterfaceTypeDefinition_Sequence
readPrec :: ReadPrec InterfaceTypeDefinition_Sequence
$creadListPrec :: ReadPrec [InterfaceTypeDefinition_Sequence]
readListPrec :: ReadPrec [InterfaceTypeDefinition_Sequence]
Read, Int -> InterfaceTypeDefinition_Sequence -> String -> String
[InterfaceTypeDefinition_Sequence] -> String -> String
InterfaceTypeDefinition_Sequence -> String
(Int -> InterfaceTypeDefinition_Sequence -> String -> String)
-> (InterfaceTypeDefinition_Sequence -> String)
-> ([InterfaceTypeDefinition_Sequence] -> String -> String)
-> Show InterfaceTypeDefinition_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InterfaceTypeDefinition_Sequence -> String -> String
showsPrec :: Int -> InterfaceTypeDefinition_Sequence -> String -> String
$cshow :: InterfaceTypeDefinition_Sequence -> String
show :: InterfaceTypeDefinition_Sequence -> String
$cshowList :: [InterfaceTypeDefinition_Sequence] -> String -> String
showList :: [InterfaceTypeDefinition_Sequence] -> String -> String
Show)
_InterfaceTypeDefinition_Sequence :: Name
_InterfaceTypeDefinition_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InterfaceTypeDefinition.Sequence")
_InterfaceTypeDefinition_Sequence_description :: Name
_InterfaceTypeDefinition_Sequence_description = (String -> Name
Core.Name String
"description")
_InterfaceTypeDefinition_Sequence_name :: Name
_InterfaceTypeDefinition_Sequence_name = (String -> Name
Core.Name String
"name")
_InterfaceTypeDefinition_Sequence_implementsInterfaces :: Name
_InterfaceTypeDefinition_Sequence_implementsInterfaces = (String -> Name
Core.Name String
"implementsInterfaces")
_InterfaceTypeDefinition_Sequence_directives :: Name
_InterfaceTypeDefinition_Sequence_directives = (String -> Name
Core.Name String
"directives")
_InterfaceTypeDefinition_Sequence_fieldsDefinition :: Name
_InterfaceTypeDefinition_Sequence_fieldsDefinition = (String -> Name
Core.Name 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
(InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool)
-> (InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool)
-> Eq InterfaceTypeDefinition_Sequence2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
== :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
$c/= :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
/= :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
Eq, Eq InterfaceTypeDefinition_Sequence2
Eq InterfaceTypeDefinition_Sequence2 =>
(InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Ordering)
-> (InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool)
-> (InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool)
-> (InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool)
-> (InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool)
-> (InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2)
-> (InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2)
-> Ord 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
$ccompare :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Ordering
compare :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Ordering
$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
>= :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2 -> Bool
$cmax :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
max :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
$cmin :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
min :: InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
-> InterfaceTypeDefinition_Sequence2
Ord, ReadPrec [InterfaceTypeDefinition_Sequence2]
ReadPrec InterfaceTypeDefinition_Sequence2
Int -> ReadS InterfaceTypeDefinition_Sequence2
ReadS [InterfaceTypeDefinition_Sequence2]
(Int -> ReadS InterfaceTypeDefinition_Sequence2)
-> ReadS [InterfaceTypeDefinition_Sequence2]
-> ReadPrec InterfaceTypeDefinition_Sequence2
-> ReadPrec [InterfaceTypeDefinition_Sequence2]
-> Read InterfaceTypeDefinition_Sequence2
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InterfaceTypeDefinition_Sequence2
readsPrec :: Int -> ReadS InterfaceTypeDefinition_Sequence2
$creadList :: ReadS [InterfaceTypeDefinition_Sequence2]
readList :: ReadS [InterfaceTypeDefinition_Sequence2]
$creadPrec :: ReadPrec InterfaceTypeDefinition_Sequence2
readPrec :: ReadPrec InterfaceTypeDefinition_Sequence2
$creadListPrec :: ReadPrec [InterfaceTypeDefinition_Sequence2]
readListPrec :: ReadPrec [InterfaceTypeDefinition_Sequence2]
Read, Int -> InterfaceTypeDefinition_Sequence2 -> String -> String
[InterfaceTypeDefinition_Sequence2] -> String -> String
InterfaceTypeDefinition_Sequence2 -> String
(Int -> InterfaceTypeDefinition_Sequence2 -> String -> String)
-> (InterfaceTypeDefinition_Sequence2 -> String)
-> ([InterfaceTypeDefinition_Sequence2] -> String -> String)
-> Show InterfaceTypeDefinition_Sequence2
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InterfaceTypeDefinition_Sequence2 -> String -> String
showsPrec :: Int -> InterfaceTypeDefinition_Sequence2 -> String -> String
$cshow :: InterfaceTypeDefinition_Sequence2 -> String
show :: InterfaceTypeDefinition_Sequence2 -> String
$cshowList :: [InterfaceTypeDefinition_Sequence2] -> String -> String
showList :: [InterfaceTypeDefinition_Sequence2] -> String -> String
Show)
_InterfaceTypeDefinition_Sequence2 :: Name
_InterfaceTypeDefinition_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InterfaceTypeDefinition.Sequence2")
_InterfaceTypeDefinition_Sequence2_description :: Name
_InterfaceTypeDefinition_Sequence2_description = (String -> Name
Core.Name String
"description")
_InterfaceTypeDefinition_Sequence2_name :: Name
_InterfaceTypeDefinition_Sequence2_name = (String -> Name
Core.Name String
"name")
_InterfaceTypeDefinition_Sequence2_implementsInterfaces :: Name
_InterfaceTypeDefinition_Sequence2_implementsInterfaces = (String -> Name
Core.Name String
"implementsInterfaces")
_InterfaceTypeDefinition_Sequence2_directives :: Name
_InterfaceTypeDefinition_Sequence2_directives = (String -> Name
Core.Name String
"directives")
data InterfaceTypeExtension =
InterfaceTypeExtensionSequence InterfaceTypeExtension_Sequence |
InterfaceTypeExtensionSequence2 InterfaceTypeExtension_Sequence2 |
InterfaceTypeExtensionSequence3 InterfaceTypeExtension_Sequence3
deriving (InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
(InterfaceTypeExtension -> InterfaceTypeExtension -> Bool)
-> (InterfaceTypeExtension -> InterfaceTypeExtension -> Bool)
-> Eq InterfaceTypeExtension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
== :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
$c/= :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
/= :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
Eq, Eq InterfaceTypeExtension
Eq InterfaceTypeExtension =>
(InterfaceTypeExtension -> InterfaceTypeExtension -> Ordering)
-> (InterfaceTypeExtension -> InterfaceTypeExtension -> Bool)
-> (InterfaceTypeExtension -> InterfaceTypeExtension -> Bool)
-> (InterfaceTypeExtension -> InterfaceTypeExtension -> Bool)
-> (InterfaceTypeExtension -> InterfaceTypeExtension -> Bool)
-> (InterfaceTypeExtension
-> InterfaceTypeExtension -> InterfaceTypeExtension)
-> (InterfaceTypeExtension
-> InterfaceTypeExtension -> InterfaceTypeExtension)
-> Ord 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
$ccompare :: InterfaceTypeExtension -> InterfaceTypeExtension -> Ordering
compare :: InterfaceTypeExtension -> InterfaceTypeExtension -> Ordering
$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
>= :: InterfaceTypeExtension -> InterfaceTypeExtension -> Bool
$cmax :: InterfaceTypeExtension
-> InterfaceTypeExtension -> InterfaceTypeExtension
max :: InterfaceTypeExtension
-> InterfaceTypeExtension -> InterfaceTypeExtension
$cmin :: InterfaceTypeExtension
-> InterfaceTypeExtension -> InterfaceTypeExtension
min :: InterfaceTypeExtension
-> InterfaceTypeExtension -> InterfaceTypeExtension
Ord, ReadPrec [InterfaceTypeExtension]
ReadPrec InterfaceTypeExtension
Int -> ReadS InterfaceTypeExtension
ReadS [InterfaceTypeExtension]
(Int -> ReadS InterfaceTypeExtension)
-> ReadS [InterfaceTypeExtension]
-> ReadPrec InterfaceTypeExtension
-> ReadPrec [InterfaceTypeExtension]
-> Read InterfaceTypeExtension
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InterfaceTypeExtension
readsPrec :: Int -> ReadS InterfaceTypeExtension
$creadList :: ReadS [InterfaceTypeExtension]
readList :: ReadS [InterfaceTypeExtension]
$creadPrec :: ReadPrec InterfaceTypeExtension
readPrec :: ReadPrec InterfaceTypeExtension
$creadListPrec :: ReadPrec [InterfaceTypeExtension]
readListPrec :: ReadPrec [InterfaceTypeExtension]
Read, Int -> InterfaceTypeExtension -> String -> String
[InterfaceTypeExtension] -> String -> String
InterfaceTypeExtension -> String
(Int -> InterfaceTypeExtension -> String -> String)
-> (InterfaceTypeExtension -> String)
-> ([InterfaceTypeExtension] -> String -> String)
-> Show InterfaceTypeExtension
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InterfaceTypeExtension -> String -> String
showsPrec :: Int -> InterfaceTypeExtension -> String -> String
$cshow :: InterfaceTypeExtension -> String
show :: InterfaceTypeExtension -> String
$cshowList :: [InterfaceTypeExtension] -> String -> String
showList :: [InterfaceTypeExtension] -> String -> String
Show)
_InterfaceTypeExtension :: Name
_InterfaceTypeExtension = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InterfaceTypeExtension")
_InterfaceTypeExtension_sequence :: Name
_InterfaceTypeExtension_sequence = (String -> Name
Core.Name String
"sequence")
_InterfaceTypeExtension_sequence2 :: Name
_InterfaceTypeExtension_sequence2 = (String -> Name
Core.Name String
"sequence2")
_InterfaceTypeExtension_sequence3 :: Name
_InterfaceTypeExtension_sequence3 = (String -> Name
Core.Name 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
(InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool)
-> (InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool)
-> Eq InterfaceTypeExtension_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
== :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
$c/= :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
/= :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
Eq, Eq InterfaceTypeExtension_Sequence
Eq InterfaceTypeExtension_Sequence =>
(InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Ordering)
-> (InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool)
-> (InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool)
-> (InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool)
-> (InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool)
-> (InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence)
-> (InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence)
-> Ord 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
$ccompare :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Ordering
compare :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Ordering
$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
>= :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence -> Bool
$cmax :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
max :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
$cmin :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
min :: InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
-> InterfaceTypeExtension_Sequence
Ord, ReadPrec [InterfaceTypeExtension_Sequence]
ReadPrec InterfaceTypeExtension_Sequence
Int -> ReadS InterfaceTypeExtension_Sequence
ReadS [InterfaceTypeExtension_Sequence]
(Int -> ReadS InterfaceTypeExtension_Sequence)
-> ReadS [InterfaceTypeExtension_Sequence]
-> ReadPrec InterfaceTypeExtension_Sequence
-> ReadPrec [InterfaceTypeExtension_Sequence]
-> Read InterfaceTypeExtension_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InterfaceTypeExtension_Sequence
readsPrec :: Int -> ReadS InterfaceTypeExtension_Sequence
$creadList :: ReadS [InterfaceTypeExtension_Sequence]
readList :: ReadS [InterfaceTypeExtension_Sequence]
$creadPrec :: ReadPrec InterfaceTypeExtension_Sequence
readPrec :: ReadPrec InterfaceTypeExtension_Sequence
$creadListPrec :: ReadPrec [InterfaceTypeExtension_Sequence]
readListPrec :: ReadPrec [InterfaceTypeExtension_Sequence]
Read, Int -> InterfaceTypeExtension_Sequence -> String -> String
[InterfaceTypeExtension_Sequence] -> String -> String
InterfaceTypeExtension_Sequence -> String
(Int -> InterfaceTypeExtension_Sequence -> String -> String)
-> (InterfaceTypeExtension_Sequence -> String)
-> ([InterfaceTypeExtension_Sequence] -> String -> String)
-> Show InterfaceTypeExtension_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InterfaceTypeExtension_Sequence -> String -> String
showsPrec :: Int -> InterfaceTypeExtension_Sequence -> String -> String
$cshow :: InterfaceTypeExtension_Sequence -> String
show :: InterfaceTypeExtension_Sequence -> String
$cshowList :: [InterfaceTypeExtension_Sequence] -> String -> String
showList :: [InterfaceTypeExtension_Sequence] -> String -> String
Show)
_InterfaceTypeExtension_Sequence :: Name
_InterfaceTypeExtension_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InterfaceTypeExtension.Sequence")
_InterfaceTypeExtension_Sequence_name :: Name
_InterfaceTypeExtension_Sequence_name = (String -> Name
Core.Name String
"name")
_InterfaceTypeExtension_Sequence_implementsInterfaces :: Name
_InterfaceTypeExtension_Sequence_implementsInterfaces = (String -> Name
Core.Name String
"implementsInterfaces")
_InterfaceTypeExtension_Sequence_directives :: Name
_InterfaceTypeExtension_Sequence_directives = (String -> Name
Core.Name String
"directives")
_InterfaceTypeExtension_Sequence_fieldsDefinition :: Name
_InterfaceTypeExtension_Sequence_fieldsDefinition = (String -> Name
Core.Name 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
(InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool)
-> (InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool)
-> Eq InterfaceTypeExtension_Sequence2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
== :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
$c/= :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
/= :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
Eq, Eq InterfaceTypeExtension_Sequence2
Eq InterfaceTypeExtension_Sequence2 =>
(InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Ordering)
-> (InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool)
-> (InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool)
-> (InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool)
-> (InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool)
-> (InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2)
-> (InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2)
-> Ord 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
$ccompare :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Ordering
compare :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Ordering
$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
>= :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2 -> Bool
$cmax :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
max :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
$cmin :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
min :: InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
-> InterfaceTypeExtension_Sequence2
Ord, ReadPrec [InterfaceTypeExtension_Sequence2]
ReadPrec InterfaceTypeExtension_Sequence2
Int -> ReadS InterfaceTypeExtension_Sequence2
ReadS [InterfaceTypeExtension_Sequence2]
(Int -> ReadS InterfaceTypeExtension_Sequence2)
-> ReadS [InterfaceTypeExtension_Sequence2]
-> ReadPrec InterfaceTypeExtension_Sequence2
-> ReadPrec [InterfaceTypeExtension_Sequence2]
-> Read InterfaceTypeExtension_Sequence2
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InterfaceTypeExtension_Sequence2
readsPrec :: Int -> ReadS InterfaceTypeExtension_Sequence2
$creadList :: ReadS [InterfaceTypeExtension_Sequence2]
readList :: ReadS [InterfaceTypeExtension_Sequence2]
$creadPrec :: ReadPrec InterfaceTypeExtension_Sequence2
readPrec :: ReadPrec InterfaceTypeExtension_Sequence2
$creadListPrec :: ReadPrec [InterfaceTypeExtension_Sequence2]
readListPrec :: ReadPrec [InterfaceTypeExtension_Sequence2]
Read, Int -> InterfaceTypeExtension_Sequence2 -> String -> String
[InterfaceTypeExtension_Sequence2] -> String -> String
InterfaceTypeExtension_Sequence2 -> String
(Int -> InterfaceTypeExtension_Sequence2 -> String -> String)
-> (InterfaceTypeExtension_Sequence2 -> String)
-> ([InterfaceTypeExtension_Sequence2] -> String -> String)
-> Show InterfaceTypeExtension_Sequence2
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InterfaceTypeExtension_Sequence2 -> String -> String
showsPrec :: Int -> InterfaceTypeExtension_Sequence2 -> String -> String
$cshow :: InterfaceTypeExtension_Sequence2 -> String
show :: InterfaceTypeExtension_Sequence2 -> String
$cshowList :: [InterfaceTypeExtension_Sequence2] -> String -> String
showList :: [InterfaceTypeExtension_Sequence2] -> String -> String
Show)
_InterfaceTypeExtension_Sequence2 :: Name
_InterfaceTypeExtension_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InterfaceTypeExtension.Sequence2")
_InterfaceTypeExtension_Sequence2_name :: Name
_InterfaceTypeExtension_Sequence2_name = (String -> Name
Core.Name String
"name")
_InterfaceTypeExtension_Sequence2_implementsInterfaces :: Name
_InterfaceTypeExtension_Sequence2_implementsInterfaces = (String -> Name
Core.Name String
"implementsInterfaces")
_InterfaceTypeExtension_Sequence2_directives :: Name
_InterfaceTypeExtension_Sequence2_directives = (String -> Name
Core.Name 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
(InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool)
-> (InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool)
-> Eq InterfaceTypeExtension_Sequence3
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
== :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
$c/= :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
/= :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
Eq, Eq InterfaceTypeExtension_Sequence3
Eq InterfaceTypeExtension_Sequence3 =>
(InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Ordering)
-> (InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool)
-> (InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool)
-> (InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool)
-> (InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool)
-> (InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3)
-> (InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3)
-> Ord 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
$ccompare :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Ordering
compare :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Ordering
$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
>= :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3 -> Bool
$cmax :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
max :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
$cmin :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
min :: InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
-> InterfaceTypeExtension_Sequence3
Ord, ReadPrec [InterfaceTypeExtension_Sequence3]
ReadPrec InterfaceTypeExtension_Sequence3
Int -> ReadS InterfaceTypeExtension_Sequence3
ReadS [InterfaceTypeExtension_Sequence3]
(Int -> ReadS InterfaceTypeExtension_Sequence3)
-> ReadS [InterfaceTypeExtension_Sequence3]
-> ReadPrec InterfaceTypeExtension_Sequence3
-> ReadPrec [InterfaceTypeExtension_Sequence3]
-> Read InterfaceTypeExtension_Sequence3
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InterfaceTypeExtension_Sequence3
readsPrec :: Int -> ReadS InterfaceTypeExtension_Sequence3
$creadList :: ReadS [InterfaceTypeExtension_Sequence3]
readList :: ReadS [InterfaceTypeExtension_Sequence3]
$creadPrec :: ReadPrec InterfaceTypeExtension_Sequence3
readPrec :: ReadPrec InterfaceTypeExtension_Sequence3
$creadListPrec :: ReadPrec [InterfaceTypeExtension_Sequence3]
readListPrec :: ReadPrec [InterfaceTypeExtension_Sequence3]
Read, Int -> InterfaceTypeExtension_Sequence3 -> String -> String
[InterfaceTypeExtension_Sequence3] -> String -> String
InterfaceTypeExtension_Sequence3 -> String
(Int -> InterfaceTypeExtension_Sequence3 -> String -> String)
-> (InterfaceTypeExtension_Sequence3 -> String)
-> ([InterfaceTypeExtension_Sequence3] -> String -> String)
-> Show InterfaceTypeExtension_Sequence3
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InterfaceTypeExtension_Sequence3 -> String -> String
showsPrec :: Int -> InterfaceTypeExtension_Sequence3 -> String -> String
$cshow :: InterfaceTypeExtension_Sequence3 -> String
show :: InterfaceTypeExtension_Sequence3 -> String
$cshowList :: [InterfaceTypeExtension_Sequence3] -> String -> String
showList :: [InterfaceTypeExtension_Sequence3] -> String -> String
Show)
_InterfaceTypeExtension_Sequence3 :: Name
_InterfaceTypeExtension_Sequence3 = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InterfaceTypeExtension.Sequence3")
_InterfaceTypeExtension_Sequence3_name :: Name
_InterfaceTypeExtension_Sequence3_name = (String -> Name
Core.Name String
"name")
_InterfaceTypeExtension_Sequence3_implementsInterfaces :: Name
_InterfaceTypeExtension_Sequence3_implementsInterfaces = (String -> Name
Core.Name 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
(UnionTypeDefinition -> UnionTypeDefinition -> Bool)
-> (UnionTypeDefinition -> UnionTypeDefinition -> Bool)
-> Eq UnionTypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
== :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
$c/= :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
/= :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
Eq, Eq UnionTypeDefinition
Eq UnionTypeDefinition =>
(UnionTypeDefinition -> UnionTypeDefinition -> Ordering)
-> (UnionTypeDefinition -> UnionTypeDefinition -> Bool)
-> (UnionTypeDefinition -> UnionTypeDefinition -> Bool)
-> (UnionTypeDefinition -> UnionTypeDefinition -> Bool)
-> (UnionTypeDefinition -> UnionTypeDefinition -> Bool)
-> (UnionTypeDefinition
-> UnionTypeDefinition -> UnionTypeDefinition)
-> (UnionTypeDefinition
-> UnionTypeDefinition -> UnionTypeDefinition)
-> Ord 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
$ccompare :: UnionTypeDefinition -> UnionTypeDefinition -> Ordering
compare :: UnionTypeDefinition -> UnionTypeDefinition -> Ordering
$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
>= :: UnionTypeDefinition -> UnionTypeDefinition -> Bool
$cmax :: UnionTypeDefinition -> UnionTypeDefinition -> UnionTypeDefinition
max :: UnionTypeDefinition -> UnionTypeDefinition -> UnionTypeDefinition
$cmin :: UnionTypeDefinition -> UnionTypeDefinition -> UnionTypeDefinition
min :: UnionTypeDefinition -> UnionTypeDefinition -> UnionTypeDefinition
Ord, ReadPrec [UnionTypeDefinition]
ReadPrec UnionTypeDefinition
Int -> ReadS UnionTypeDefinition
ReadS [UnionTypeDefinition]
(Int -> ReadS UnionTypeDefinition)
-> ReadS [UnionTypeDefinition]
-> ReadPrec UnionTypeDefinition
-> ReadPrec [UnionTypeDefinition]
-> Read UnionTypeDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnionTypeDefinition
readsPrec :: Int -> ReadS UnionTypeDefinition
$creadList :: ReadS [UnionTypeDefinition]
readList :: ReadS [UnionTypeDefinition]
$creadPrec :: ReadPrec UnionTypeDefinition
readPrec :: ReadPrec UnionTypeDefinition
$creadListPrec :: ReadPrec [UnionTypeDefinition]
readListPrec :: ReadPrec [UnionTypeDefinition]
Read, Int -> UnionTypeDefinition -> String -> String
[UnionTypeDefinition] -> String -> String
UnionTypeDefinition -> String
(Int -> UnionTypeDefinition -> String -> String)
-> (UnionTypeDefinition -> String)
-> ([UnionTypeDefinition] -> String -> String)
-> Show UnionTypeDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> UnionTypeDefinition -> String -> String
showsPrec :: Int -> UnionTypeDefinition -> String -> String
$cshow :: UnionTypeDefinition -> String
show :: UnionTypeDefinition -> String
$cshowList :: [UnionTypeDefinition] -> String -> String
showList :: [UnionTypeDefinition] -> String -> String
Show)
_UnionTypeDefinition :: Name
_UnionTypeDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.UnionTypeDefinition")
_UnionTypeDefinition_description :: Name
_UnionTypeDefinition_description = (String -> Name
Core.Name String
"description")
_UnionTypeDefinition_name :: Name
_UnionTypeDefinition_name = (String -> Name
Core.Name String
"name")
_UnionTypeDefinition_directives :: Name
_UnionTypeDefinition_directives = (String -> Name
Core.Name String
"directives")
_UnionTypeDefinition_unionMemberTypes :: Name
_UnionTypeDefinition_unionMemberTypes = (String -> Name
Core.Name String
"unionMemberTypes")
data UnionMemberTypes =
UnionMemberTypesSequence UnionMemberTypes_Sequence |
UnionMemberTypesSequence2 UnionMemberTypes_Sequence2
deriving (UnionMemberTypes -> UnionMemberTypes -> Bool
(UnionMemberTypes -> UnionMemberTypes -> Bool)
-> (UnionMemberTypes -> UnionMemberTypes -> Bool)
-> Eq UnionMemberTypes
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnionMemberTypes -> UnionMemberTypes -> Bool
== :: UnionMemberTypes -> UnionMemberTypes -> Bool
$c/= :: UnionMemberTypes -> UnionMemberTypes -> Bool
/= :: UnionMemberTypes -> UnionMemberTypes -> Bool
Eq, Eq UnionMemberTypes
Eq UnionMemberTypes =>
(UnionMemberTypes -> UnionMemberTypes -> Ordering)
-> (UnionMemberTypes -> UnionMemberTypes -> Bool)
-> (UnionMemberTypes -> UnionMemberTypes -> Bool)
-> (UnionMemberTypes -> UnionMemberTypes -> Bool)
-> (UnionMemberTypes -> UnionMemberTypes -> Bool)
-> (UnionMemberTypes -> UnionMemberTypes -> UnionMemberTypes)
-> (UnionMemberTypes -> UnionMemberTypes -> UnionMemberTypes)
-> Ord 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
$ccompare :: UnionMemberTypes -> UnionMemberTypes -> Ordering
compare :: UnionMemberTypes -> UnionMemberTypes -> Ordering
$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
>= :: UnionMemberTypes -> UnionMemberTypes -> Bool
$cmax :: UnionMemberTypes -> UnionMemberTypes -> UnionMemberTypes
max :: UnionMemberTypes -> UnionMemberTypes -> UnionMemberTypes
$cmin :: UnionMemberTypes -> UnionMemberTypes -> UnionMemberTypes
min :: UnionMemberTypes -> UnionMemberTypes -> UnionMemberTypes
Ord, ReadPrec [UnionMemberTypes]
ReadPrec UnionMemberTypes
Int -> ReadS UnionMemberTypes
ReadS [UnionMemberTypes]
(Int -> ReadS UnionMemberTypes)
-> ReadS [UnionMemberTypes]
-> ReadPrec UnionMemberTypes
-> ReadPrec [UnionMemberTypes]
-> Read UnionMemberTypes
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnionMemberTypes
readsPrec :: Int -> ReadS UnionMemberTypes
$creadList :: ReadS [UnionMemberTypes]
readList :: ReadS [UnionMemberTypes]
$creadPrec :: ReadPrec UnionMemberTypes
readPrec :: ReadPrec UnionMemberTypes
$creadListPrec :: ReadPrec [UnionMemberTypes]
readListPrec :: ReadPrec [UnionMemberTypes]
Read, Int -> UnionMemberTypes -> String -> String
[UnionMemberTypes] -> String -> String
UnionMemberTypes -> String
(Int -> UnionMemberTypes -> String -> String)
-> (UnionMemberTypes -> String)
-> ([UnionMemberTypes] -> String -> String)
-> Show UnionMemberTypes
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> UnionMemberTypes -> String -> String
showsPrec :: Int -> UnionMemberTypes -> String -> String
$cshow :: UnionMemberTypes -> String
show :: UnionMemberTypes -> String
$cshowList :: [UnionMemberTypes] -> String -> String
showList :: [UnionMemberTypes] -> String -> String
Show)
_UnionMemberTypes :: Name
_UnionMemberTypes = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.UnionMemberTypes")
_UnionMemberTypes_sequence :: Name
_UnionMemberTypes_sequence = (String -> Name
Core.Name String
"sequence")
_UnionMemberTypes_sequence2 :: Name
_UnionMemberTypes_sequence2 = (String -> Name
Core.Name 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
(UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool)
-> (UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool)
-> Eq UnionMemberTypes_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
== :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
$c/= :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
/= :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
Eq, Eq UnionMemberTypes_Sequence
Eq UnionMemberTypes_Sequence =>
(UnionMemberTypes_Sequence
-> UnionMemberTypes_Sequence -> Ordering)
-> (UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool)
-> (UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool)
-> (UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool)
-> (UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool)
-> (UnionMemberTypes_Sequence
-> UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence)
-> (UnionMemberTypes_Sequence
-> UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence)
-> Ord 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
$ccompare :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Ordering
compare :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Ordering
$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
>= :: UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence -> Bool
$cmax :: UnionMemberTypes_Sequence
-> UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence
max :: UnionMemberTypes_Sequence
-> UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence
$cmin :: UnionMemberTypes_Sequence
-> UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence
min :: UnionMemberTypes_Sequence
-> UnionMemberTypes_Sequence -> UnionMemberTypes_Sequence
Ord, ReadPrec [UnionMemberTypes_Sequence]
ReadPrec UnionMemberTypes_Sequence
Int -> ReadS UnionMemberTypes_Sequence
ReadS [UnionMemberTypes_Sequence]
(Int -> ReadS UnionMemberTypes_Sequence)
-> ReadS [UnionMemberTypes_Sequence]
-> ReadPrec UnionMemberTypes_Sequence
-> ReadPrec [UnionMemberTypes_Sequence]
-> Read UnionMemberTypes_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnionMemberTypes_Sequence
readsPrec :: Int -> ReadS UnionMemberTypes_Sequence
$creadList :: ReadS [UnionMemberTypes_Sequence]
readList :: ReadS [UnionMemberTypes_Sequence]
$creadPrec :: ReadPrec UnionMemberTypes_Sequence
readPrec :: ReadPrec UnionMemberTypes_Sequence
$creadListPrec :: ReadPrec [UnionMemberTypes_Sequence]
readListPrec :: ReadPrec [UnionMemberTypes_Sequence]
Read, Int -> UnionMemberTypes_Sequence -> String -> String
[UnionMemberTypes_Sequence] -> String -> String
UnionMemberTypes_Sequence -> String
(Int -> UnionMemberTypes_Sequence -> String -> String)
-> (UnionMemberTypes_Sequence -> String)
-> ([UnionMemberTypes_Sequence] -> String -> String)
-> Show UnionMemberTypes_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> UnionMemberTypes_Sequence -> String -> String
showsPrec :: Int -> UnionMemberTypes_Sequence -> String -> String
$cshow :: UnionMemberTypes_Sequence -> String
show :: UnionMemberTypes_Sequence -> String
$cshowList :: [UnionMemberTypes_Sequence] -> String -> String
showList :: [UnionMemberTypes_Sequence] -> String -> String
Show)
_UnionMemberTypes_Sequence :: Name
_UnionMemberTypes_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.UnionMemberTypes.Sequence")
_UnionMemberTypes_Sequence_unionMemberTypes :: Name
_UnionMemberTypes_Sequence_unionMemberTypes = (String -> Name
Core.Name String
"unionMemberTypes")
_UnionMemberTypes_Sequence_namedType :: Name
_UnionMemberTypes_Sequence_namedType = (String -> Name
Core.Name 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
(UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool)
-> (UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> Bool)
-> Eq UnionMemberTypes_Sequence2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
== :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
$c/= :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
/= :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
Eq, Eq UnionMemberTypes_Sequence2
Eq UnionMemberTypes_Sequence2 =>
(UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> Ordering)
-> (UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> Bool)
-> (UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> Bool)
-> (UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> Bool)
-> (UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> Bool)
-> (UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2)
-> (UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2)
-> Ord 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
$ccompare :: UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> Ordering
compare :: UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> Ordering
$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
>= :: UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2 -> Bool
$cmax :: UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2
max :: UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2
$cmin :: UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2
min :: UnionMemberTypes_Sequence2
-> UnionMemberTypes_Sequence2 -> UnionMemberTypes_Sequence2
Ord, ReadPrec [UnionMemberTypes_Sequence2]
ReadPrec UnionMemberTypes_Sequence2
Int -> ReadS UnionMemberTypes_Sequence2
ReadS [UnionMemberTypes_Sequence2]
(Int -> ReadS UnionMemberTypes_Sequence2)
-> ReadS [UnionMemberTypes_Sequence2]
-> ReadPrec UnionMemberTypes_Sequence2
-> ReadPrec [UnionMemberTypes_Sequence2]
-> Read UnionMemberTypes_Sequence2
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnionMemberTypes_Sequence2
readsPrec :: Int -> ReadS UnionMemberTypes_Sequence2
$creadList :: ReadS [UnionMemberTypes_Sequence2]
readList :: ReadS [UnionMemberTypes_Sequence2]
$creadPrec :: ReadPrec UnionMemberTypes_Sequence2
readPrec :: ReadPrec UnionMemberTypes_Sequence2
$creadListPrec :: ReadPrec [UnionMemberTypes_Sequence2]
readListPrec :: ReadPrec [UnionMemberTypes_Sequence2]
Read, Int -> UnionMemberTypes_Sequence2 -> String -> String
[UnionMemberTypes_Sequence2] -> String -> String
UnionMemberTypes_Sequence2 -> String
(Int -> UnionMemberTypes_Sequence2 -> String -> String)
-> (UnionMemberTypes_Sequence2 -> String)
-> ([UnionMemberTypes_Sequence2] -> String -> String)
-> Show UnionMemberTypes_Sequence2
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> UnionMemberTypes_Sequence2 -> String -> String
showsPrec :: Int -> UnionMemberTypes_Sequence2 -> String -> String
$cshow :: UnionMemberTypes_Sequence2 -> String
show :: UnionMemberTypes_Sequence2 -> String
$cshowList :: [UnionMemberTypes_Sequence2] -> String -> String
showList :: [UnionMemberTypes_Sequence2] -> String -> String
Show)
_UnionMemberTypes_Sequence2 :: Name
_UnionMemberTypes_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.UnionMemberTypes.Sequence2")
_UnionMemberTypes_Sequence2_or :: Name
_UnionMemberTypes_Sequence2_or = (String -> Name
Core.Name String
"or")
_UnionMemberTypes_Sequence2_namedType :: Name
_UnionMemberTypes_Sequence2_namedType = (String -> Name
Core.Name String
"namedType")
data UnionTypeExtension =
UnionTypeExtensionSequence UnionTypeExtension_Sequence |
UnionTypeExtensionSequence2 UnionTypeExtension_Sequence2
deriving (UnionTypeExtension -> UnionTypeExtension -> Bool
(UnionTypeExtension -> UnionTypeExtension -> Bool)
-> (UnionTypeExtension -> UnionTypeExtension -> Bool)
-> Eq UnionTypeExtension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnionTypeExtension -> UnionTypeExtension -> Bool
== :: UnionTypeExtension -> UnionTypeExtension -> Bool
$c/= :: UnionTypeExtension -> UnionTypeExtension -> Bool
/= :: UnionTypeExtension -> UnionTypeExtension -> Bool
Eq, Eq UnionTypeExtension
Eq UnionTypeExtension =>
(UnionTypeExtension -> UnionTypeExtension -> Ordering)
-> (UnionTypeExtension -> UnionTypeExtension -> Bool)
-> (UnionTypeExtension -> UnionTypeExtension -> Bool)
-> (UnionTypeExtension -> UnionTypeExtension -> Bool)
-> (UnionTypeExtension -> UnionTypeExtension -> Bool)
-> (UnionTypeExtension -> UnionTypeExtension -> UnionTypeExtension)
-> (UnionTypeExtension -> UnionTypeExtension -> UnionTypeExtension)
-> Ord 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
$ccompare :: UnionTypeExtension -> UnionTypeExtension -> Ordering
compare :: UnionTypeExtension -> UnionTypeExtension -> Ordering
$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
>= :: UnionTypeExtension -> UnionTypeExtension -> Bool
$cmax :: UnionTypeExtension -> UnionTypeExtension -> UnionTypeExtension
max :: UnionTypeExtension -> UnionTypeExtension -> UnionTypeExtension
$cmin :: UnionTypeExtension -> UnionTypeExtension -> UnionTypeExtension
min :: UnionTypeExtension -> UnionTypeExtension -> UnionTypeExtension
Ord, ReadPrec [UnionTypeExtension]
ReadPrec UnionTypeExtension
Int -> ReadS UnionTypeExtension
ReadS [UnionTypeExtension]
(Int -> ReadS UnionTypeExtension)
-> ReadS [UnionTypeExtension]
-> ReadPrec UnionTypeExtension
-> ReadPrec [UnionTypeExtension]
-> Read UnionTypeExtension
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnionTypeExtension
readsPrec :: Int -> ReadS UnionTypeExtension
$creadList :: ReadS [UnionTypeExtension]
readList :: ReadS [UnionTypeExtension]
$creadPrec :: ReadPrec UnionTypeExtension
readPrec :: ReadPrec UnionTypeExtension
$creadListPrec :: ReadPrec [UnionTypeExtension]
readListPrec :: ReadPrec [UnionTypeExtension]
Read, Int -> UnionTypeExtension -> String -> String
[UnionTypeExtension] -> String -> String
UnionTypeExtension -> String
(Int -> UnionTypeExtension -> String -> String)
-> (UnionTypeExtension -> String)
-> ([UnionTypeExtension] -> String -> String)
-> Show UnionTypeExtension
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> UnionTypeExtension -> String -> String
showsPrec :: Int -> UnionTypeExtension -> String -> String
$cshow :: UnionTypeExtension -> String
show :: UnionTypeExtension -> String
$cshowList :: [UnionTypeExtension] -> String -> String
showList :: [UnionTypeExtension] -> String -> String
Show)
_UnionTypeExtension :: Name
_UnionTypeExtension = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.UnionTypeExtension")
_UnionTypeExtension_sequence :: Name
_UnionTypeExtension_sequence = (String -> Name
Core.Name String
"sequence")
_UnionTypeExtension_sequence2 :: Name
_UnionTypeExtension_sequence2 = (String -> Name
Core.Name 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
(UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> Bool)
-> (UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> Bool)
-> Eq UnionTypeExtension_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
== :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
$c/= :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
/= :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
Eq, Eq UnionTypeExtension_Sequence
Eq UnionTypeExtension_Sequence =>
(UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> Ordering)
-> (UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> Bool)
-> (UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> Bool)
-> (UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> Bool)
-> (UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> Bool)
-> (UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence)
-> (UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence)
-> Ord 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
$ccompare :: UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> Ordering
compare :: UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> Ordering
$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
>= :: UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence -> Bool
$cmax :: UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence
max :: UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence
$cmin :: UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence
min :: UnionTypeExtension_Sequence
-> UnionTypeExtension_Sequence -> UnionTypeExtension_Sequence
Ord, ReadPrec [UnionTypeExtension_Sequence]
ReadPrec UnionTypeExtension_Sequence
Int -> ReadS UnionTypeExtension_Sequence
ReadS [UnionTypeExtension_Sequence]
(Int -> ReadS UnionTypeExtension_Sequence)
-> ReadS [UnionTypeExtension_Sequence]
-> ReadPrec UnionTypeExtension_Sequence
-> ReadPrec [UnionTypeExtension_Sequence]
-> Read UnionTypeExtension_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnionTypeExtension_Sequence
readsPrec :: Int -> ReadS UnionTypeExtension_Sequence
$creadList :: ReadS [UnionTypeExtension_Sequence]
readList :: ReadS [UnionTypeExtension_Sequence]
$creadPrec :: ReadPrec UnionTypeExtension_Sequence
readPrec :: ReadPrec UnionTypeExtension_Sequence
$creadListPrec :: ReadPrec [UnionTypeExtension_Sequence]
readListPrec :: ReadPrec [UnionTypeExtension_Sequence]
Read, Int -> UnionTypeExtension_Sequence -> String -> String
[UnionTypeExtension_Sequence] -> String -> String
UnionTypeExtension_Sequence -> String
(Int -> UnionTypeExtension_Sequence -> String -> String)
-> (UnionTypeExtension_Sequence -> String)
-> ([UnionTypeExtension_Sequence] -> String -> String)
-> Show UnionTypeExtension_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> UnionTypeExtension_Sequence -> String -> String
showsPrec :: Int -> UnionTypeExtension_Sequence -> String -> String
$cshow :: UnionTypeExtension_Sequence -> String
show :: UnionTypeExtension_Sequence -> String
$cshowList :: [UnionTypeExtension_Sequence] -> String -> String
showList :: [UnionTypeExtension_Sequence] -> String -> String
Show)
_UnionTypeExtension_Sequence :: Name
_UnionTypeExtension_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.UnionTypeExtension.Sequence")
_UnionTypeExtension_Sequence_name :: Name
_UnionTypeExtension_Sequence_name = (String -> Name
Core.Name String
"name")
_UnionTypeExtension_Sequence_directives :: Name
_UnionTypeExtension_Sequence_directives = (String -> Name
Core.Name String
"directives")
_UnionTypeExtension_Sequence_unionMemberTypes :: Name
_UnionTypeExtension_Sequence_unionMemberTypes = (String -> Name
Core.Name 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
(UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool)
-> (UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool)
-> Eq UnionTypeExtension_Sequence2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
== :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
$c/= :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
/= :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
Eq, Eq UnionTypeExtension_Sequence2
Eq UnionTypeExtension_Sequence2 =>
(UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Ordering)
-> (UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool)
-> (UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool)
-> (UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool)
-> (UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool)
-> (UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> UnionTypeExtension_Sequence2)
-> (UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> UnionTypeExtension_Sequence2)
-> Ord 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
$ccompare :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Ordering
compare :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Ordering
$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
>= :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> Bool
$cmax :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> UnionTypeExtension_Sequence2
max :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> UnionTypeExtension_Sequence2
$cmin :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> UnionTypeExtension_Sequence2
min :: UnionTypeExtension_Sequence2
-> UnionTypeExtension_Sequence2 -> UnionTypeExtension_Sequence2
Ord, ReadPrec [UnionTypeExtension_Sequence2]
ReadPrec UnionTypeExtension_Sequence2
Int -> ReadS UnionTypeExtension_Sequence2
ReadS [UnionTypeExtension_Sequence2]
(Int -> ReadS UnionTypeExtension_Sequence2)
-> ReadS [UnionTypeExtension_Sequence2]
-> ReadPrec UnionTypeExtension_Sequence2
-> ReadPrec [UnionTypeExtension_Sequence2]
-> Read UnionTypeExtension_Sequence2
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS UnionTypeExtension_Sequence2
readsPrec :: Int -> ReadS UnionTypeExtension_Sequence2
$creadList :: ReadS [UnionTypeExtension_Sequence2]
readList :: ReadS [UnionTypeExtension_Sequence2]
$creadPrec :: ReadPrec UnionTypeExtension_Sequence2
readPrec :: ReadPrec UnionTypeExtension_Sequence2
$creadListPrec :: ReadPrec [UnionTypeExtension_Sequence2]
readListPrec :: ReadPrec [UnionTypeExtension_Sequence2]
Read, Int -> UnionTypeExtension_Sequence2 -> String -> String
[UnionTypeExtension_Sequence2] -> String -> String
UnionTypeExtension_Sequence2 -> String
(Int -> UnionTypeExtension_Sequence2 -> String -> String)
-> (UnionTypeExtension_Sequence2 -> String)
-> ([UnionTypeExtension_Sequence2] -> String -> String)
-> Show UnionTypeExtension_Sequence2
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> UnionTypeExtension_Sequence2 -> String -> String
showsPrec :: Int -> UnionTypeExtension_Sequence2 -> String -> String
$cshow :: UnionTypeExtension_Sequence2 -> String
show :: UnionTypeExtension_Sequence2 -> String
$cshowList :: [UnionTypeExtension_Sequence2] -> String -> String
showList :: [UnionTypeExtension_Sequence2] -> String -> String
Show)
_UnionTypeExtension_Sequence2 :: Name
_UnionTypeExtension_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.UnionTypeExtension.Sequence2")
_UnionTypeExtension_Sequence2_name :: Name
_UnionTypeExtension_Sequence2_name = (String -> Name
Core.Name String
"name")
_UnionTypeExtension_Sequence2_directives :: Name
_UnionTypeExtension_Sequence2_directives = (String -> Name
Core.Name String
"directives")
data EnumTypeDefinition =
EnumTypeDefinition {
EnumTypeDefinition -> Maybe Description
enumTypeDefinitionDescription :: (Maybe Description),
EnumTypeDefinition -> Name
enumTypeDefinitionName :: Name,
EnumTypeDefinition -> Maybe Directives
enumTypeDefinitionDirectives :: (Maybe Directives),
EnumTypeDefinition -> Maybe EnumValuesDefinition
enumTypeDefinitionEnumValuesDefinition :: (Maybe EnumValuesDefinition)}
deriving (EnumTypeDefinition -> EnumTypeDefinition -> Bool
(EnumTypeDefinition -> EnumTypeDefinition -> Bool)
-> (EnumTypeDefinition -> EnumTypeDefinition -> Bool)
-> Eq EnumTypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
== :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
$c/= :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
/= :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
Eq, Eq EnumTypeDefinition
Eq EnumTypeDefinition =>
(EnumTypeDefinition -> EnumTypeDefinition -> Ordering)
-> (EnumTypeDefinition -> EnumTypeDefinition -> Bool)
-> (EnumTypeDefinition -> EnumTypeDefinition -> Bool)
-> (EnumTypeDefinition -> EnumTypeDefinition -> Bool)
-> (EnumTypeDefinition -> EnumTypeDefinition -> Bool)
-> (EnumTypeDefinition -> EnumTypeDefinition -> EnumTypeDefinition)
-> (EnumTypeDefinition -> EnumTypeDefinition -> EnumTypeDefinition)
-> Ord 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
$ccompare :: EnumTypeDefinition -> EnumTypeDefinition -> Ordering
compare :: EnumTypeDefinition -> EnumTypeDefinition -> Ordering
$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
>= :: EnumTypeDefinition -> EnumTypeDefinition -> Bool
$cmax :: EnumTypeDefinition -> EnumTypeDefinition -> EnumTypeDefinition
max :: EnumTypeDefinition -> EnumTypeDefinition -> EnumTypeDefinition
$cmin :: EnumTypeDefinition -> EnumTypeDefinition -> EnumTypeDefinition
min :: EnumTypeDefinition -> EnumTypeDefinition -> EnumTypeDefinition
Ord, ReadPrec [EnumTypeDefinition]
ReadPrec EnumTypeDefinition
Int -> ReadS EnumTypeDefinition
ReadS [EnumTypeDefinition]
(Int -> ReadS EnumTypeDefinition)
-> ReadS [EnumTypeDefinition]
-> ReadPrec EnumTypeDefinition
-> ReadPrec [EnumTypeDefinition]
-> Read EnumTypeDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EnumTypeDefinition
readsPrec :: Int -> ReadS EnumTypeDefinition
$creadList :: ReadS [EnumTypeDefinition]
readList :: ReadS [EnumTypeDefinition]
$creadPrec :: ReadPrec EnumTypeDefinition
readPrec :: ReadPrec EnumTypeDefinition
$creadListPrec :: ReadPrec [EnumTypeDefinition]
readListPrec :: ReadPrec [EnumTypeDefinition]
Read, Int -> EnumTypeDefinition -> String -> String
[EnumTypeDefinition] -> String -> String
EnumTypeDefinition -> String
(Int -> EnumTypeDefinition -> String -> String)
-> (EnumTypeDefinition -> String)
-> ([EnumTypeDefinition] -> String -> String)
-> Show EnumTypeDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> EnumTypeDefinition -> String -> String
showsPrec :: Int -> EnumTypeDefinition -> String -> String
$cshow :: EnumTypeDefinition -> String
show :: EnumTypeDefinition -> String
$cshowList :: [EnumTypeDefinition] -> String -> String
showList :: [EnumTypeDefinition] -> String -> String
Show)
_EnumTypeDefinition :: Name
_EnumTypeDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.EnumTypeDefinition")
_EnumTypeDefinition_description :: Name
_EnumTypeDefinition_description = (String -> Name
Core.Name String
"description")
_EnumTypeDefinition_name :: Name
_EnumTypeDefinition_name = (String -> Name
Core.Name String
"name")
_EnumTypeDefinition_directives :: Name
_EnumTypeDefinition_directives = (String -> Name
Core.Name String
"directives")
_EnumTypeDefinition_enumValuesDefinition :: Name
_EnumTypeDefinition_enumValuesDefinition = (String -> Name
Core.Name String
"enumValuesDefinition")
newtype EnumValuesDefinition =
EnumValuesDefinition {
EnumValuesDefinition -> [EnumValueDefinition]
unEnumValuesDefinition :: [EnumValueDefinition]}
deriving (EnumValuesDefinition -> EnumValuesDefinition -> Bool
(EnumValuesDefinition -> EnumValuesDefinition -> Bool)
-> (EnumValuesDefinition -> EnumValuesDefinition -> Bool)
-> Eq EnumValuesDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
== :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
$c/= :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
/= :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
Eq, Eq EnumValuesDefinition
Eq EnumValuesDefinition =>
(EnumValuesDefinition -> EnumValuesDefinition -> Ordering)
-> (EnumValuesDefinition -> EnumValuesDefinition -> Bool)
-> (EnumValuesDefinition -> EnumValuesDefinition -> Bool)
-> (EnumValuesDefinition -> EnumValuesDefinition -> Bool)
-> (EnumValuesDefinition -> EnumValuesDefinition -> Bool)
-> (EnumValuesDefinition
-> EnumValuesDefinition -> EnumValuesDefinition)
-> (EnumValuesDefinition
-> EnumValuesDefinition -> EnumValuesDefinition)
-> Ord 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
$ccompare :: EnumValuesDefinition -> EnumValuesDefinition -> Ordering
compare :: EnumValuesDefinition -> EnumValuesDefinition -> Ordering
$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
>= :: EnumValuesDefinition -> EnumValuesDefinition -> Bool
$cmax :: EnumValuesDefinition
-> EnumValuesDefinition -> EnumValuesDefinition
max :: EnumValuesDefinition
-> EnumValuesDefinition -> EnumValuesDefinition
$cmin :: EnumValuesDefinition
-> EnumValuesDefinition -> EnumValuesDefinition
min :: EnumValuesDefinition
-> EnumValuesDefinition -> EnumValuesDefinition
Ord, ReadPrec [EnumValuesDefinition]
ReadPrec EnumValuesDefinition
Int -> ReadS EnumValuesDefinition
ReadS [EnumValuesDefinition]
(Int -> ReadS EnumValuesDefinition)
-> ReadS [EnumValuesDefinition]
-> ReadPrec EnumValuesDefinition
-> ReadPrec [EnumValuesDefinition]
-> Read EnumValuesDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EnumValuesDefinition
readsPrec :: Int -> ReadS EnumValuesDefinition
$creadList :: ReadS [EnumValuesDefinition]
readList :: ReadS [EnumValuesDefinition]
$creadPrec :: ReadPrec EnumValuesDefinition
readPrec :: ReadPrec EnumValuesDefinition
$creadListPrec :: ReadPrec [EnumValuesDefinition]
readListPrec :: ReadPrec [EnumValuesDefinition]
Read, Int -> EnumValuesDefinition -> String -> String
[EnumValuesDefinition] -> String -> String
EnumValuesDefinition -> String
(Int -> EnumValuesDefinition -> String -> String)
-> (EnumValuesDefinition -> String)
-> ([EnumValuesDefinition] -> String -> String)
-> Show EnumValuesDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> EnumValuesDefinition -> String -> String
showsPrec :: Int -> EnumValuesDefinition -> String -> String
$cshow :: EnumValuesDefinition -> String
show :: EnumValuesDefinition -> String
$cshowList :: [EnumValuesDefinition] -> String -> String
showList :: [EnumValuesDefinition] -> String -> String
Show)
_EnumValuesDefinition :: Name
_EnumValuesDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.EnumValuesDefinition")
data EnumValueDefinition =
EnumValueDefinition {
EnumValueDefinition -> Maybe Description
enumValueDefinitionDescription :: (Maybe Description),
EnumValueDefinition -> EnumValue
enumValueDefinitionEnumValue :: EnumValue,
EnumValueDefinition -> Maybe Directives
enumValueDefinitionDirectives :: (Maybe Directives)}
deriving (EnumValueDefinition -> EnumValueDefinition -> Bool
(EnumValueDefinition -> EnumValueDefinition -> Bool)
-> (EnumValueDefinition -> EnumValueDefinition -> Bool)
-> Eq EnumValueDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EnumValueDefinition -> EnumValueDefinition -> Bool
== :: EnumValueDefinition -> EnumValueDefinition -> Bool
$c/= :: EnumValueDefinition -> EnumValueDefinition -> Bool
/= :: EnumValueDefinition -> EnumValueDefinition -> Bool
Eq, Eq EnumValueDefinition
Eq EnumValueDefinition =>
(EnumValueDefinition -> EnumValueDefinition -> Ordering)
-> (EnumValueDefinition -> EnumValueDefinition -> Bool)
-> (EnumValueDefinition -> EnumValueDefinition -> Bool)
-> (EnumValueDefinition -> EnumValueDefinition -> Bool)
-> (EnumValueDefinition -> EnumValueDefinition -> Bool)
-> (EnumValueDefinition
-> EnumValueDefinition -> EnumValueDefinition)
-> (EnumValueDefinition
-> EnumValueDefinition -> EnumValueDefinition)
-> Ord 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
$ccompare :: EnumValueDefinition -> EnumValueDefinition -> Ordering
compare :: EnumValueDefinition -> EnumValueDefinition -> Ordering
$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
>= :: EnumValueDefinition -> EnumValueDefinition -> Bool
$cmax :: EnumValueDefinition -> EnumValueDefinition -> EnumValueDefinition
max :: EnumValueDefinition -> EnumValueDefinition -> EnumValueDefinition
$cmin :: EnumValueDefinition -> EnumValueDefinition -> EnumValueDefinition
min :: EnumValueDefinition -> EnumValueDefinition -> EnumValueDefinition
Ord, ReadPrec [EnumValueDefinition]
ReadPrec EnumValueDefinition
Int -> ReadS EnumValueDefinition
ReadS [EnumValueDefinition]
(Int -> ReadS EnumValueDefinition)
-> ReadS [EnumValueDefinition]
-> ReadPrec EnumValueDefinition
-> ReadPrec [EnumValueDefinition]
-> Read EnumValueDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EnumValueDefinition
readsPrec :: Int -> ReadS EnumValueDefinition
$creadList :: ReadS [EnumValueDefinition]
readList :: ReadS [EnumValueDefinition]
$creadPrec :: ReadPrec EnumValueDefinition
readPrec :: ReadPrec EnumValueDefinition
$creadListPrec :: ReadPrec [EnumValueDefinition]
readListPrec :: ReadPrec [EnumValueDefinition]
Read, Int -> EnumValueDefinition -> String -> String
[EnumValueDefinition] -> String -> String
EnumValueDefinition -> String
(Int -> EnumValueDefinition -> String -> String)
-> (EnumValueDefinition -> String)
-> ([EnumValueDefinition] -> String -> String)
-> Show EnumValueDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> EnumValueDefinition -> String -> String
showsPrec :: Int -> EnumValueDefinition -> String -> String
$cshow :: EnumValueDefinition -> String
show :: EnumValueDefinition -> String
$cshowList :: [EnumValueDefinition] -> String -> String
showList :: [EnumValueDefinition] -> String -> String
Show)
_EnumValueDefinition :: Name
_EnumValueDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.EnumValueDefinition")
_EnumValueDefinition_description :: Name
_EnumValueDefinition_description = (String -> Name
Core.Name String
"description")
_EnumValueDefinition_enumValue :: Name
_EnumValueDefinition_enumValue = (String -> Name
Core.Name String
"enumValue")
_EnumValueDefinition_directives :: Name
_EnumValueDefinition_directives = (String -> Name
Core.Name String
"directives")
data EnumTypeExtension =
EnumTypeExtensionSequence EnumTypeExtension_Sequence |
EnumTypeExtensionSequence2 EnumTypeExtension_Sequence2
deriving (EnumTypeExtension -> EnumTypeExtension -> Bool
(EnumTypeExtension -> EnumTypeExtension -> Bool)
-> (EnumTypeExtension -> EnumTypeExtension -> Bool)
-> Eq EnumTypeExtension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EnumTypeExtension -> EnumTypeExtension -> Bool
== :: EnumTypeExtension -> EnumTypeExtension -> Bool
$c/= :: EnumTypeExtension -> EnumTypeExtension -> Bool
/= :: EnumTypeExtension -> EnumTypeExtension -> Bool
Eq, Eq EnumTypeExtension
Eq EnumTypeExtension =>
(EnumTypeExtension -> EnumTypeExtension -> Ordering)
-> (EnumTypeExtension -> EnumTypeExtension -> Bool)
-> (EnumTypeExtension -> EnumTypeExtension -> Bool)
-> (EnumTypeExtension -> EnumTypeExtension -> Bool)
-> (EnumTypeExtension -> EnumTypeExtension -> Bool)
-> (EnumTypeExtension -> EnumTypeExtension -> EnumTypeExtension)
-> (EnumTypeExtension -> EnumTypeExtension -> EnumTypeExtension)
-> Ord 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
$ccompare :: EnumTypeExtension -> EnumTypeExtension -> Ordering
compare :: EnumTypeExtension -> EnumTypeExtension -> Ordering
$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
>= :: EnumTypeExtension -> EnumTypeExtension -> Bool
$cmax :: EnumTypeExtension -> EnumTypeExtension -> EnumTypeExtension
max :: EnumTypeExtension -> EnumTypeExtension -> EnumTypeExtension
$cmin :: EnumTypeExtension -> EnumTypeExtension -> EnumTypeExtension
min :: EnumTypeExtension -> EnumTypeExtension -> EnumTypeExtension
Ord, ReadPrec [EnumTypeExtension]
ReadPrec EnumTypeExtension
Int -> ReadS EnumTypeExtension
ReadS [EnumTypeExtension]
(Int -> ReadS EnumTypeExtension)
-> ReadS [EnumTypeExtension]
-> ReadPrec EnumTypeExtension
-> ReadPrec [EnumTypeExtension]
-> Read EnumTypeExtension
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EnumTypeExtension
readsPrec :: Int -> ReadS EnumTypeExtension
$creadList :: ReadS [EnumTypeExtension]
readList :: ReadS [EnumTypeExtension]
$creadPrec :: ReadPrec EnumTypeExtension
readPrec :: ReadPrec EnumTypeExtension
$creadListPrec :: ReadPrec [EnumTypeExtension]
readListPrec :: ReadPrec [EnumTypeExtension]
Read, Int -> EnumTypeExtension -> String -> String
[EnumTypeExtension] -> String -> String
EnumTypeExtension -> String
(Int -> EnumTypeExtension -> String -> String)
-> (EnumTypeExtension -> String)
-> ([EnumTypeExtension] -> String -> String)
-> Show EnumTypeExtension
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> EnumTypeExtension -> String -> String
showsPrec :: Int -> EnumTypeExtension -> String -> String
$cshow :: EnumTypeExtension -> String
show :: EnumTypeExtension -> String
$cshowList :: [EnumTypeExtension] -> String -> String
showList :: [EnumTypeExtension] -> String -> String
Show)
_EnumTypeExtension :: Name
_EnumTypeExtension = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.EnumTypeExtension")
_EnumTypeExtension_sequence :: Name
_EnumTypeExtension_sequence = (String -> Name
Core.Name String
"sequence")
_EnumTypeExtension_sequence2 :: Name
_EnumTypeExtension_sequence2 = (String -> Name
Core.Name 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
(EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool)
-> (EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> Bool)
-> Eq EnumTypeExtension_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
== :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
$c/= :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
/= :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
Eq, Eq EnumTypeExtension_Sequence
Eq EnumTypeExtension_Sequence =>
(EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> Ordering)
-> (EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> Bool)
-> (EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> Bool)
-> (EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> Bool)
-> (EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> Bool)
-> (EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence)
-> (EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence)
-> Ord 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
$ccompare :: EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> Ordering
compare :: EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> Ordering
$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
>= :: EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence -> Bool
$cmax :: EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence
max :: EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence
$cmin :: EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence
min :: EnumTypeExtension_Sequence
-> EnumTypeExtension_Sequence -> EnumTypeExtension_Sequence
Ord, ReadPrec [EnumTypeExtension_Sequence]
ReadPrec EnumTypeExtension_Sequence
Int -> ReadS EnumTypeExtension_Sequence
ReadS [EnumTypeExtension_Sequence]
(Int -> ReadS EnumTypeExtension_Sequence)
-> ReadS [EnumTypeExtension_Sequence]
-> ReadPrec EnumTypeExtension_Sequence
-> ReadPrec [EnumTypeExtension_Sequence]
-> Read EnumTypeExtension_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EnumTypeExtension_Sequence
readsPrec :: Int -> ReadS EnumTypeExtension_Sequence
$creadList :: ReadS [EnumTypeExtension_Sequence]
readList :: ReadS [EnumTypeExtension_Sequence]
$creadPrec :: ReadPrec EnumTypeExtension_Sequence
readPrec :: ReadPrec EnumTypeExtension_Sequence
$creadListPrec :: ReadPrec [EnumTypeExtension_Sequence]
readListPrec :: ReadPrec [EnumTypeExtension_Sequence]
Read, Int -> EnumTypeExtension_Sequence -> String -> String
[EnumTypeExtension_Sequence] -> String -> String
EnumTypeExtension_Sequence -> String
(Int -> EnumTypeExtension_Sequence -> String -> String)
-> (EnumTypeExtension_Sequence -> String)
-> ([EnumTypeExtension_Sequence] -> String -> String)
-> Show EnumTypeExtension_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> EnumTypeExtension_Sequence -> String -> String
showsPrec :: Int -> EnumTypeExtension_Sequence -> String -> String
$cshow :: EnumTypeExtension_Sequence -> String
show :: EnumTypeExtension_Sequence -> String
$cshowList :: [EnumTypeExtension_Sequence] -> String -> String
showList :: [EnumTypeExtension_Sequence] -> String -> String
Show)
_EnumTypeExtension_Sequence :: Name
_EnumTypeExtension_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.EnumTypeExtension.Sequence")
_EnumTypeExtension_Sequence_name :: Name
_EnumTypeExtension_Sequence_name = (String -> Name
Core.Name String
"name")
_EnumTypeExtension_Sequence_directives :: Name
_EnumTypeExtension_Sequence_directives = (String -> Name
Core.Name String
"directives")
_EnumTypeExtension_Sequence_enumValuesDefinition :: Name
_EnumTypeExtension_Sequence_enumValuesDefinition = (String -> Name
Core.Name 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
(EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> Bool)
-> (EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> Bool)
-> Eq EnumTypeExtension_Sequence2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
== :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
$c/= :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
/= :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
Eq, Eq EnumTypeExtension_Sequence2
Eq EnumTypeExtension_Sequence2 =>
(EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> Ordering)
-> (EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> Bool)
-> (EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> Bool)
-> (EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> Bool)
-> (EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> Bool)
-> (EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2)
-> (EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2)
-> Ord 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
$ccompare :: EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> Ordering
compare :: EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> Ordering
$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
>= :: EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2 -> Bool
$cmax :: EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2
max :: EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2
$cmin :: EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2
min :: EnumTypeExtension_Sequence2
-> EnumTypeExtension_Sequence2 -> EnumTypeExtension_Sequence2
Ord, ReadPrec [EnumTypeExtension_Sequence2]
ReadPrec EnumTypeExtension_Sequence2
Int -> ReadS EnumTypeExtension_Sequence2
ReadS [EnumTypeExtension_Sequence2]
(Int -> ReadS EnumTypeExtension_Sequence2)
-> ReadS [EnumTypeExtension_Sequence2]
-> ReadPrec EnumTypeExtension_Sequence2
-> ReadPrec [EnumTypeExtension_Sequence2]
-> Read EnumTypeExtension_Sequence2
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS EnumTypeExtension_Sequence2
readsPrec :: Int -> ReadS EnumTypeExtension_Sequence2
$creadList :: ReadS [EnumTypeExtension_Sequence2]
readList :: ReadS [EnumTypeExtension_Sequence2]
$creadPrec :: ReadPrec EnumTypeExtension_Sequence2
readPrec :: ReadPrec EnumTypeExtension_Sequence2
$creadListPrec :: ReadPrec [EnumTypeExtension_Sequence2]
readListPrec :: ReadPrec [EnumTypeExtension_Sequence2]
Read, Int -> EnumTypeExtension_Sequence2 -> String -> String
[EnumTypeExtension_Sequence2] -> String -> String
EnumTypeExtension_Sequence2 -> String
(Int -> EnumTypeExtension_Sequence2 -> String -> String)
-> (EnumTypeExtension_Sequence2 -> String)
-> ([EnumTypeExtension_Sequence2] -> String -> String)
-> Show EnumTypeExtension_Sequence2
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> EnumTypeExtension_Sequence2 -> String -> String
showsPrec :: Int -> EnumTypeExtension_Sequence2 -> String -> String
$cshow :: EnumTypeExtension_Sequence2 -> String
show :: EnumTypeExtension_Sequence2 -> String
$cshowList :: [EnumTypeExtension_Sequence2] -> String -> String
showList :: [EnumTypeExtension_Sequence2] -> String -> String
Show)
_EnumTypeExtension_Sequence2 :: Name
_EnumTypeExtension_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.EnumTypeExtension.Sequence2")
_EnumTypeExtension_Sequence2_name :: Name
_EnumTypeExtension_Sequence2_name = (String -> Name
Core.Name String
"name")
_EnumTypeExtension_Sequence2_directives :: Name
_EnumTypeExtension_Sequence2_directives = (String -> Name
Core.Name String
"directives")
data InputObjectTypeDefinition =
InputObjectTypeDefinitionSequence InputObjectTypeDefinition_Sequence |
InputObjectTypeDefinitionSequence2 InputObjectTypeDefinition_Sequence2
deriving (InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
(InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool)
-> (InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool)
-> Eq InputObjectTypeDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
== :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
$c/= :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
/= :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
Eq, Eq InputObjectTypeDefinition
Eq InputObjectTypeDefinition =>
(InputObjectTypeDefinition
-> InputObjectTypeDefinition -> Ordering)
-> (InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool)
-> (InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool)
-> (InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool)
-> (InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool)
-> (InputObjectTypeDefinition
-> InputObjectTypeDefinition -> InputObjectTypeDefinition)
-> (InputObjectTypeDefinition
-> InputObjectTypeDefinition -> InputObjectTypeDefinition)
-> Ord 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
$ccompare :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Ordering
compare :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Ordering
$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
>= :: InputObjectTypeDefinition -> InputObjectTypeDefinition -> Bool
$cmax :: InputObjectTypeDefinition
-> InputObjectTypeDefinition -> InputObjectTypeDefinition
max :: InputObjectTypeDefinition
-> InputObjectTypeDefinition -> InputObjectTypeDefinition
$cmin :: InputObjectTypeDefinition
-> InputObjectTypeDefinition -> InputObjectTypeDefinition
min :: InputObjectTypeDefinition
-> InputObjectTypeDefinition -> InputObjectTypeDefinition
Ord, ReadPrec [InputObjectTypeDefinition]
ReadPrec InputObjectTypeDefinition
Int -> ReadS InputObjectTypeDefinition
ReadS [InputObjectTypeDefinition]
(Int -> ReadS InputObjectTypeDefinition)
-> ReadS [InputObjectTypeDefinition]
-> ReadPrec InputObjectTypeDefinition
-> ReadPrec [InputObjectTypeDefinition]
-> Read InputObjectTypeDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InputObjectTypeDefinition
readsPrec :: Int -> ReadS InputObjectTypeDefinition
$creadList :: ReadS [InputObjectTypeDefinition]
readList :: ReadS [InputObjectTypeDefinition]
$creadPrec :: ReadPrec InputObjectTypeDefinition
readPrec :: ReadPrec InputObjectTypeDefinition
$creadListPrec :: ReadPrec [InputObjectTypeDefinition]
readListPrec :: ReadPrec [InputObjectTypeDefinition]
Read, Int -> InputObjectTypeDefinition -> String -> String
[InputObjectTypeDefinition] -> String -> String
InputObjectTypeDefinition -> String
(Int -> InputObjectTypeDefinition -> String -> String)
-> (InputObjectTypeDefinition -> String)
-> ([InputObjectTypeDefinition] -> String -> String)
-> Show InputObjectTypeDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InputObjectTypeDefinition -> String -> String
showsPrec :: Int -> InputObjectTypeDefinition -> String -> String
$cshow :: InputObjectTypeDefinition -> String
show :: InputObjectTypeDefinition -> String
$cshowList :: [InputObjectTypeDefinition] -> String -> String
showList :: [InputObjectTypeDefinition] -> String -> String
Show)
_InputObjectTypeDefinition :: Name
_InputObjectTypeDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InputObjectTypeDefinition")
_InputObjectTypeDefinition_sequence :: Name
_InputObjectTypeDefinition_sequence = (String -> Name
Core.Name String
"sequence")
_InputObjectTypeDefinition_sequence2 :: Name
_InputObjectTypeDefinition_sequence2 = (String -> Name
Core.Name 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
(InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool)
-> (InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool)
-> Eq InputObjectTypeDefinition_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
== :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
$c/= :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
/= :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
Eq, Eq InputObjectTypeDefinition_Sequence
Eq InputObjectTypeDefinition_Sequence =>
(InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Ordering)
-> (InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool)
-> (InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool)
-> (InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool)
-> (InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool)
-> (InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence)
-> (InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence)
-> Ord 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
$ccompare :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Ordering
compare :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Ordering
$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
>= :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence -> Bool
$cmax :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
max :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
$cmin :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
min :: InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
-> InputObjectTypeDefinition_Sequence
Ord, ReadPrec [InputObjectTypeDefinition_Sequence]
ReadPrec InputObjectTypeDefinition_Sequence
Int -> ReadS InputObjectTypeDefinition_Sequence
ReadS [InputObjectTypeDefinition_Sequence]
(Int -> ReadS InputObjectTypeDefinition_Sequence)
-> ReadS [InputObjectTypeDefinition_Sequence]
-> ReadPrec InputObjectTypeDefinition_Sequence
-> ReadPrec [InputObjectTypeDefinition_Sequence]
-> Read InputObjectTypeDefinition_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InputObjectTypeDefinition_Sequence
readsPrec :: Int -> ReadS InputObjectTypeDefinition_Sequence
$creadList :: ReadS [InputObjectTypeDefinition_Sequence]
readList :: ReadS [InputObjectTypeDefinition_Sequence]
$creadPrec :: ReadPrec InputObjectTypeDefinition_Sequence
readPrec :: ReadPrec InputObjectTypeDefinition_Sequence
$creadListPrec :: ReadPrec [InputObjectTypeDefinition_Sequence]
readListPrec :: ReadPrec [InputObjectTypeDefinition_Sequence]
Read, Int -> InputObjectTypeDefinition_Sequence -> String -> String
[InputObjectTypeDefinition_Sequence] -> String -> String
InputObjectTypeDefinition_Sequence -> String
(Int -> InputObjectTypeDefinition_Sequence -> String -> String)
-> (InputObjectTypeDefinition_Sequence -> String)
-> ([InputObjectTypeDefinition_Sequence] -> String -> String)
-> Show InputObjectTypeDefinition_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InputObjectTypeDefinition_Sequence -> String -> String
showsPrec :: Int -> InputObjectTypeDefinition_Sequence -> String -> String
$cshow :: InputObjectTypeDefinition_Sequence -> String
show :: InputObjectTypeDefinition_Sequence -> String
$cshowList :: [InputObjectTypeDefinition_Sequence] -> String -> String
showList :: [InputObjectTypeDefinition_Sequence] -> String -> String
Show)
_InputObjectTypeDefinition_Sequence :: Name
_InputObjectTypeDefinition_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InputObjectTypeDefinition.Sequence")
_InputObjectTypeDefinition_Sequence_description :: Name
_InputObjectTypeDefinition_Sequence_description = (String -> Name
Core.Name String
"description")
_InputObjectTypeDefinition_Sequence_name :: Name
_InputObjectTypeDefinition_Sequence_name = (String -> Name
Core.Name String
"name")
_InputObjectTypeDefinition_Sequence_directives :: Name
_InputObjectTypeDefinition_Sequence_directives = (String -> Name
Core.Name String
"directives")
_InputObjectTypeDefinition_Sequence_inputFieldsDefinition :: Name
_InputObjectTypeDefinition_Sequence_inputFieldsDefinition = (String -> Name
Core.Name 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
(InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool)
-> (InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool)
-> Eq InputObjectTypeDefinition_Sequence2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
== :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
$c/= :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
/= :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
Eq, Eq InputObjectTypeDefinition_Sequence2
Eq InputObjectTypeDefinition_Sequence2 =>
(InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Ordering)
-> (InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool)
-> (InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool)
-> (InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool)
-> (InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool)
-> (InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2)
-> (InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2)
-> Ord 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
$ccompare :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Ordering
compare :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Ordering
$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
>= :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2 -> Bool
$cmax :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
max :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
$cmin :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
min :: InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
-> InputObjectTypeDefinition_Sequence2
Ord, ReadPrec [InputObjectTypeDefinition_Sequence2]
ReadPrec InputObjectTypeDefinition_Sequence2
Int -> ReadS InputObjectTypeDefinition_Sequence2
ReadS [InputObjectTypeDefinition_Sequence2]
(Int -> ReadS InputObjectTypeDefinition_Sequence2)
-> ReadS [InputObjectTypeDefinition_Sequence2]
-> ReadPrec InputObjectTypeDefinition_Sequence2
-> ReadPrec [InputObjectTypeDefinition_Sequence2]
-> Read InputObjectTypeDefinition_Sequence2
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InputObjectTypeDefinition_Sequence2
readsPrec :: Int -> ReadS InputObjectTypeDefinition_Sequence2
$creadList :: ReadS [InputObjectTypeDefinition_Sequence2]
readList :: ReadS [InputObjectTypeDefinition_Sequence2]
$creadPrec :: ReadPrec InputObjectTypeDefinition_Sequence2
readPrec :: ReadPrec InputObjectTypeDefinition_Sequence2
$creadListPrec :: ReadPrec [InputObjectTypeDefinition_Sequence2]
readListPrec :: ReadPrec [InputObjectTypeDefinition_Sequence2]
Read, Int -> InputObjectTypeDefinition_Sequence2 -> String -> String
[InputObjectTypeDefinition_Sequence2] -> String -> String
InputObjectTypeDefinition_Sequence2 -> String
(Int -> InputObjectTypeDefinition_Sequence2 -> String -> String)
-> (InputObjectTypeDefinition_Sequence2 -> String)
-> ([InputObjectTypeDefinition_Sequence2] -> String -> String)
-> Show InputObjectTypeDefinition_Sequence2
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InputObjectTypeDefinition_Sequence2 -> String -> String
showsPrec :: Int -> InputObjectTypeDefinition_Sequence2 -> String -> String
$cshow :: InputObjectTypeDefinition_Sequence2 -> String
show :: InputObjectTypeDefinition_Sequence2 -> String
$cshowList :: [InputObjectTypeDefinition_Sequence2] -> String -> String
showList :: [InputObjectTypeDefinition_Sequence2] -> String -> String
Show)
_InputObjectTypeDefinition_Sequence2 :: Name
_InputObjectTypeDefinition_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InputObjectTypeDefinition.Sequence2")
_InputObjectTypeDefinition_Sequence2_description :: Name
_InputObjectTypeDefinition_Sequence2_description = (String -> Name
Core.Name String
"description")
_InputObjectTypeDefinition_Sequence2_name :: Name
_InputObjectTypeDefinition_Sequence2_name = (String -> Name
Core.Name String
"name")
_InputObjectTypeDefinition_Sequence2_directives :: Name
_InputObjectTypeDefinition_Sequence2_directives = (String -> Name
Core.Name String
"directives")
newtype InputFieldsDefinition =
InputFieldsDefinition {
InputFieldsDefinition -> [InputValueDefinition]
unInputFieldsDefinition :: [InputValueDefinition]}
deriving (InputFieldsDefinition -> InputFieldsDefinition -> Bool
(InputFieldsDefinition -> InputFieldsDefinition -> Bool)
-> (InputFieldsDefinition -> InputFieldsDefinition -> Bool)
-> Eq InputFieldsDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
== :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
$c/= :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
/= :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
Eq, Eq InputFieldsDefinition
Eq InputFieldsDefinition =>
(InputFieldsDefinition -> InputFieldsDefinition -> Ordering)
-> (InputFieldsDefinition -> InputFieldsDefinition -> Bool)
-> (InputFieldsDefinition -> InputFieldsDefinition -> Bool)
-> (InputFieldsDefinition -> InputFieldsDefinition -> Bool)
-> (InputFieldsDefinition -> InputFieldsDefinition -> Bool)
-> (InputFieldsDefinition
-> InputFieldsDefinition -> InputFieldsDefinition)
-> (InputFieldsDefinition
-> InputFieldsDefinition -> InputFieldsDefinition)
-> Ord 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
$ccompare :: InputFieldsDefinition -> InputFieldsDefinition -> Ordering
compare :: InputFieldsDefinition -> InputFieldsDefinition -> Ordering
$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
>= :: InputFieldsDefinition -> InputFieldsDefinition -> Bool
$cmax :: InputFieldsDefinition
-> InputFieldsDefinition -> InputFieldsDefinition
max :: InputFieldsDefinition
-> InputFieldsDefinition -> InputFieldsDefinition
$cmin :: InputFieldsDefinition
-> InputFieldsDefinition -> InputFieldsDefinition
min :: InputFieldsDefinition
-> InputFieldsDefinition -> InputFieldsDefinition
Ord, ReadPrec [InputFieldsDefinition]
ReadPrec InputFieldsDefinition
Int -> ReadS InputFieldsDefinition
ReadS [InputFieldsDefinition]
(Int -> ReadS InputFieldsDefinition)
-> ReadS [InputFieldsDefinition]
-> ReadPrec InputFieldsDefinition
-> ReadPrec [InputFieldsDefinition]
-> Read InputFieldsDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InputFieldsDefinition
readsPrec :: Int -> ReadS InputFieldsDefinition
$creadList :: ReadS [InputFieldsDefinition]
readList :: ReadS [InputFieldsDefinition]
$creadPrec :: ReadPrec InputFieldsDefinition
readPrec :: ReadPrec InputFieldsDefinition
$creadListPrec :: ReadPrec [InputFieldsDefinition]
readListPrec :: ReadPrec [InputFieldsDefinition]
Read, Int -> InputFieldsDefinition -> String -> String
[InputFieldsDefinition] -> String -> String
InputFieldsDefinition -> String
(Int -> InputFieldsDefinition -> String -> String)
-> (InputFieldsDefinition -> String)
-> ([InputFieldsDefinition] -> String -> String)
-> Show InputFieldsDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InputFieldsDefinition -> String -> String
showsPrec :: Int -> InputFieldsDefinition -> String -> String
$cshow :: InputFieldsDefinition -> String
show :: InputFieldsDefinition -> String
$cshowList :: [InputFieldsDefinition] -> String -> String
showList :: [InputFieldsDefinition] -> String -> String
Show)
_InputFieldsDefinition :: Name
_InputFieldsDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InputFieldsDefinition")
data InputObjectTypeExtension =
InputObjectTypeExtensionSequence InputObjectTypeExtension_Sequence |
InputObjectTypeExtensionSequence2 InputObjectTypeExtension_Sequence2
deriving (InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
(InputObjectTypeExtension -> InputObjectTypeExtension -> Bool)
-> (InputObjectTypeExtension -> InputObjectTypeExtension -> Bool)
-> Eq InputObjectTypeExtension
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
== :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
$c/= :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
/= :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
Eq, Eq InputObjectTypeExtension
Eq InputObjectTypeExtension =>
(InputObjectTypeExtension -> InputObjectTypeExtension -> Ordering)
-> (InputObjectTypeExtension -> InputObjectTypeExtension -> Bool)
-> (InputObjectTypeExtension -> InputObjectTypeExtension -> Bool)
-> (InputObjectTypeExtension -> InputObjectTypeExtension -> Bool)
-> (InputObjectTypeExtension -> InputObjectTypeExtension -> Bool)
-> (InputObjectTypeExtension
-> InputObjectTypeExtension -> InputObjectTypeExtension)
-> (InputObjectTypeExtension
-> InputObjectTypeExtension -> InputObjectTypeExtension)
-> Ord 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
$ccompare :: InputObjectTypeExtension -> InputObjectTypeExtension -> Ordering
compare :: InputObjectTypeExtension -> InputObjectTypeExtension -> Ordering
$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
>= :: InputObjectTypeExtension -> InputObjectTypeExtension -> Bool
$cmax :: InputObjectTypeExtension
-> InputObjectTypeExtension -> InputObjectTypeExtension
max :: InputObjectTypeExtension
-> InputObjectTypeExtension -> InputObjectTypeExtension
$cmin :: InputObjectTypeExtension
-> InputObjectTypeExtension -> InputObjectTypeExtension
min :: InputObjectTypeExtension
-> InputObjectTypeExtension -> InputObjectTypeExtension
Ord, ReadPrec [InputObjectTypeExtension]
ReadPrec InputObjectTypeExtension
Int -> ReadS InputObjectTypeExtension
ReadS [InputObjectTypeExtension]
(Int -> ReadS InputObjectTypeExtension)
-> ReadS [InputObjectTypeExtension]
-> ReadPrec InputObjectTypeExtension
-> ReadPrec [InputObjectTypeExtension]
-> Read InputObjectTypeExtension
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InputObjectTypeExtension
readsPrec :: Int -> ReadS InputObjectTypeExtension
$creadList :: ReadS [InputObjectTypeExtension]
readList :: ReadS [InputObjectTypeExtension]
$creadPrec :: ReadPrec InputObjectTypeExtension
readPrec :: ReadPrec InputObjectTypeExtension
$creadListPrec :: ReadPrec [InputObjectTypeExtension]
readListPrec :: ReadPrec [InputObjectTypeExtension]
Read, Int -> InputObjectTypeExtension -> String -> String
[InputObjectTypeExtension] -> String -> String
InputObjectTypeExtension -> String
(Int -> InputObjectTypeExtension -> String -> String)
-> (InputObjectTypeExtension -> String)
-> ([InputObjectTypeExtension] -> String -> String)
-> Show InputObjectTypeExtension
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InputObjectTypeExtension -> String -> String
showsPrec :: Int -> InputObjectTypeExtension -> String -> String
$cshow :: InputObjectTypeExtension -> String
show :: InputObjectTypeExtension -> String
$cshowList :: [InputObjectTypeExtension] -> String -> String
showList :: [InputObjectTypeExtension] -> String -> String
Show)
_InputObjectTypeExtension :: Name
_InputObjectTypeExtension = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InputObjectTypeExtension")
_InputObjectTypeExtension_sequence :: Name
_InputObjectTypeExtension_sequence = (String -> Name
Core.Name String
"sequence")
_InputObjectTypeExtension_sequence2 :: Name
_InputObjectTypeExtension_sequence2 = (String -> Name
Core.Name 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
(InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool)
-> (InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool)
-> Eq InputObjectTypeExtension_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
== :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
$c/= :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
/= :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
Eq, Eq InputObjectTypeExtension_Sequence
Eq InputObjectTypeExtension_Sequence =>
(InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Ordering)
-> (InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool)
-> (InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool)
-> (InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool)
-> (InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool)
-> (InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence)
-> (InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence)
-> Ord 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
$ccompare :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Ordering
compare :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Ordering
$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
>= :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence -> Bool
$cmax :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
max :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
$cmin :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
min :: InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
-> InputObjectTypeExtension_Sequence
Ord, ReadPrec [InputObjectTypeExtension_Sequence]
ReadPrec InputObjectTypeExtension_Sequence
Int -> ReadS InputObjectTypeExtension_Sequence
ReadS [InputObjectTypeExtension_Sequence]
(Int -> ReadS InputObjectTypeExtension_Sequence)
-> ReadS [InputObjectTypeExtension_Sequence]
-> ReadPrec InputObjectTypeExtension_Sequence
-> ReadPrec [InputObjectTypeExtension_Sequence]
-> Read InputObjectTypeExtension_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InputObjectTypeExtension_Sequence
readsPrec :: Int -> ReadS InputObjectTypeExtension_Sequence
$creadList :: ReadS [InputObjectTypeExtension_Sequence]
readList :: ReadS [InputObjectTypeExtension_Sequence]
$creadPrec :: ReadPrec InputObjectTypeExtension_Sequence
readPrec :: ReadPrec InputObjectTypeExtension_Sequence
$creadListPrec :: ReadPrec [InputObjectTypeExtension_Sequence]
readListPrec :: ReadPrec [InputObjectTypeExtension_Sequence]
Read, Int -> InputObjectTypeExtension_Sequence -> String -> String
[InputObjectTypeExtension_Sequence] -> String -> String
InputObjectTypeExtension_Sequence -> String
(Int -> InputObjectTypeExtension_Sequence -> String -> String)
-> (InputObjectTypeExtension_Sequence -> String)
-> ([InputObjectTypeExtension_Sequence] -> String -> String)
-> Show InputObjectTypeExtension_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InputObjectTypeExtension_Sequence -> String -> String
showsPrec :: Int -> InputObjectTypeExtension_Sequence -> String -> String
$cshow :: InputObjectTypeExtension_Sequence -> String
show :: InputObjectTypeExtension_Sequence -> String
$cshowList :: [InputObjectTypeExtension_Sequence] -> String -> String
showList :: [InputObjectTypeExtension_Sequence] -> String -> String
Show)
_InputObjectTypeExtension_Sequence :: Name
_InputObjectTypeExtension_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InputObjectTypeExtension.Sequence")
_InputObjectTypeExtension_Sequence_name :: Name
_InputObjectTypeExtension_Sequence_name = (String -> Name
Core.Name String
"name")
_InputObjectTypeExtension_Sequence_directives :: Name
_InputObjectTypeExtension_Sequence_directives = (String -> Name
Core.Name String
"directives")
_InputObjectTypeExtension_Sequence_inputFieldsDefinition :: Name
_InputObjectTypeExtension_Sequence_inputFieldsDefinition = (String -> Name
Core.Name 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
(InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool)
-> (InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool)
-> Eq InputObjectTypeExtension_Sequence2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
== :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
$c/= :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
/= :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
Eq, Eq InputObjectTypeExtension_Sequence2
Eq InputObjectTypeExtension_Sequence2 =>
(InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Ordering)
-> (InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool)
-> (InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool)
-> (InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool)
-> (InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool)
-> (InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2)
-> (InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2)
-> Ord 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
$ccompare :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Ordering
compare :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Ordering
$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
>= :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2 -> Bool
$cmax :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
max :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
$cmin :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
min :: InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
-> InputObjectTypeExtension_Sequence2
Ord, ReadPrec [InputObjectTypeExtension_Sequence2]
ReadPrec InputObjectTypeExtension_Sequence2
Int -> ReadS InputObjectTypeExtension_Sequence2
ReadS [InputObjectTypeExtension_Sequence2]
(Int -> ReadS InputObjectTypeExtension_Sequence2)
-> ReadS [InputObjectTypeExtension_Sequence2]
-> ReadPrec InputObjectTypeExtension_Sequence2
-> ReadPrec [InputObjectTypeExtension_Sequence2]
-> Read InputObjectTypeExtension_Sequence2
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS InputObjectTypeExtension_Sequence2
readsPrec :: Int -> ReadS InputObjectTypeExtension_Sequence2
$creadList :: ReadS [InputObjectTypeExtension_Sequence2]
readList :: ReadS [InputObjectTypeExtension_Sequence2]
$creadPrec :: ReadPrec InputObjectTypeExtension_Sequence2
readPrec :: ReadPrec InputObjectTypeExtension_Sequence2
$creadListPrec :: ReadPrec [InputObjectTypeExtension_Sequence2]
readListPrec :: ReadPrec [InputObjectTypeExtension_Sequence2]
Read, Int -> InputObjectTypeExtension_Sequence2 -> String -> String
[InputObjectTypeExtension_Sequence2] -> String -> String
InputObjectTypeExtension_Sequence2 -> String
(Int -> InputObjectTypeExtension_Sequence2 -> String -> String)
-> (InputObjectTypeExtension_Sequence2 -> String)
-> ([InputObjectTypeExtension_Sequence2] -> String -> String)
-> Show InputObjectTypeExtension_Sequence2
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> InputObjectTypeExtension_Sequence2 -> String -> String
showsPrec :: Int -> InputObjectTypeExtension_Sequence2 -> String -> String
$cshow :: InputObjectTypeExtension_Sequence2 -> String
show :: InputObjectTypeExtension_Sequence2 -> String
$cshowList :: [InputObjectTypeExtension_Sequence2] -> String -> String
showList :: [InputObjectTypeExtension_Sequence2] -> String -> String
Show)
_InputObjectTypeExtension_Sequence2 :: Name
_InputObjectTypeExtension_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.InputObjectTypeExtension.Sequence2")
_InputObjectTypeExtension_Sequence2_name :: Name
_InputObjectTypeExtension_Sequence2_name = (String -> Name
Core.Name String
"name")
_InputObjectTypeExtension_Sequence2_directives :: Name
_InputObjectTypeExtension_Sequence2_directives = (String -> Name
Core.Name 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
(DirectiveDefinition -> DirectiveDefinition -> Bool)
-> (DirectiveDefinition -> DirectiveDefinition -> Bool)
-> Eq DirectiveDefinition
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DirectiveDefinition -> DirectiveDefinition -> Bool
== :: DirectiveDefinition -> DirectiveDefinition -> Bool
$c/= :: DirectiveDefinition -> DirectiveDefinition -> Bool
/= :: DirectiveDefinition -> DirectiveDefinition -> Bool
Eq, Eq DirectiveDefinition
Eq DirectiveDefinition =>
(DirectiveDefinition -> DirectiveDefinition -> Ordering)
-> (DirectiveDefinition -> DirectiveDefinition -> Bool)
-> (DirectiveDefinition -> DirectiveDefinition -> Bool)
-> (DirectiveDefinition -> DirectiveDefinition -> Bool)
-> (DirectiveDefinition -> DirectiveDefinition -> Bool)
-> (DirectiveDefinition
-> DirectiveDefinition -> DirectiveDefinition)
-> (DirectiveDefinition
-> DirectiveDefinition -> DirectiveDefinition)
-> Ord 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
$ccompare :: DirectiveDefinition -> DirectiveDefinition -> Ordering
compare :: DirectiveDefinition -> DirectiveDefinition -> Ordering
$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
>= :: DirectiveDefinition -> DirectiveDefinition -> Bool
$cmax :: DirectiveDefinition -> DirectiveDefinition -> DirectiveDefinition
max :: DirectiveDefinition -> DirectiveDefinition -> DirectiveDefinition
$cmin :: DirectiveDefinition -> DirectiveDefinition -> DirectiveDefinition
min :: DirectiveDefinition -> DirectiveDefinition -> DirectiveDefinition
Ord, ReadPrec [DirectiveDefinition]
ReadPrec DirectiveDefinition
Int -> ReadS DirectiveDefinition
ReadS [DirectiveDefinition]
(Int -> ReadS DirectiveDefinition)
-> ReadS [DirectiveDefinition]
-> ReadPrec DirectiveDefinition
-> ReadPrec [DirectiveDefinition]
-> Read DirectiveDefinition
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DirectiveDefinition
readsPrec :: Int -> ReadS DirectiveDefinition
$creadList :: ReadS [DirectiveDefinition]
readList :: ReadS [DirectiveDefinition]
$creadPrec :: ReadPrec DirectiveDefinition
readPrec :: ReadPrec DirectiveDefinition
$creadListPrec :: ReadPrec [DirectiveDefinition]
readListPrec :: ReadPrec [DirectiveDefinition]
Read, Int -> DirectiveDefinition -> String -> String
[DirectiveDefinition] -> String -> String
DirectiveDefinition -> String
(Int -> DirectiveDefinition -> String -> String)
-> (DirectiveDefinition -> String)
-> ([DirectiveDefinition] -> String -> String)
-> Show DirectiveDefinition
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> DirectiveDefinition -> String -> String
showsPrec :: Int -> DirectiveDefinition -> String -> String
$cshow :: DirectiveDefinition -> String
show :: DirectiveDefinition -> String
$cshowList :: [DirectiveDefinition] -> String -> String
showList :: [DirectiveDefinition] -> String -> String
Show)
_DirectiveDefinition :: Name
_DirectiveDefinition = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.DirectiveDefinition")
_DirectiveDefinition_description :: Name
_DirectiveDefinition_description = (String -> Name
Core.Name String
"description")
_DirectiveDefinition_name :: Name
_DirectiveDefinition_name = (String -> Name
Core.Name String
"name")
_DirectiveDefinition_argumentsDefinition :: Name
_DirectiveDefinition_argumentsDefinition = (String -> Name
Core.Name String
"argumentsDefinition")
_DirectiveDefinition_repeatable :: Name
_DirectiveDefinition_repeatable = (String -> Name
Core.Name String
"repeatable")
_DirectiveDefinition_directiveLocations :: Name
_DirectiveDefinition_directiveLocations = (String -> Name
Core.Name String
"directiveLocations")
data DirectiveLocations =
DirectiveLocationsSequence DirectiveLocations_Sequence |
DirectiveLocationsSequence2 DirectiveLocations_Sequence2
deriving (DirectiveLocations -> DirectiveLocations -> Bool
(DirectiveLocations -> DirectiveLocations -> Bool)
-> (DirectiveLocations -> DirectiveLocations -> Bool)
-> Eq DirectiveLocations
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DirectiveLocations -> DirectiveLocations -> Bool
== :: DirectiveLocations -> DirectiveLocations -> Bool
$c/= :: DirectiveLocations -> DirectiveLocations -> Bool
/= :: DirectiveLocations -> DirectiveLocations -> Bool
Eq, Eq DirectiveLocations
Eq DirectiveLocations =>
(DirectiveLocations -> DirectiveLocations -> Ordering)
-> (DirectiveLocations -> DirectiveLocations -> Bool)
-> (DirectiveLocations -> DirectiveLocations -> Bool)
-> (DirectiveLocations -> DirectiveLocations -> Bool)
-> (DirectiveLocations -> DirectiveLocations -> Bool)
-> (DirectiveLocations -> DirectiveLocations -> DirectiveLocations)
-> (DirectiveLocations -> DirectiveLocations -> DirectiveLocations)
-> Ord 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
$ccompare :: DirectiveLocations -> DirectiveLocations -> Ordering
compare :: DirectiveLocations -> DirectiveLocations -> Ordering
$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
>= :: DirectiveLocations -> DirectiveLocations -> Bool
$cmax :: DirectiveLocations -> DirectiveLocations -> DirectiveLocations
max :: DirectiveLocations -> DirectiveLocations -> DirectiveLocations
$cmin :: DirectiveLocations -> DirectiveLocations -> DirectiveLocations
min :: DirectiveLocations -> DirectiveLocations -> DirectiveLocations
Ord, ReadPrec [DirectiveLocations]
ReadPrec DirectiveLocations
Int -> ReadS DirectiveLocations
ReadS [DirectiveLocations]
(Int -> ReadS DirectiveLocations)
-> ReadS [DirectiveLocations]
-> ReadPrec DirectiveLocations
-> ReadPrec [DirectiveLocations]
-> Read DirectiveLocations
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DirectiveLocations
readsPrec :: Int -> ReadS DirectiveLocations
$creadList :: ReadS [DirectiveLocations]
readList :: ReadS [DirectiveLocations]
$creadPrec :: ReadPrec DirectiveLocations
readPrec :: ReadPrec DirectiveLocations
$creadListPrec :: ReadPrec [DirectiveLocations]
readListPrec :: ReadPrec [DirectiveLocations]
Read, Int -> DirectiveLocations -> String -> String
[DirectiveLocations] -> String -> String
DirectiveLocations -> String
(Int -> DirectiveLocations -> String -> String)
-> (DirectiveLocations -> String)
-> ([DirectiveLocations] -> String -> String)
-> Show DirectiveLocations
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> DirectiveLocations -> String -> String
showsPrec :: Int -> DirectiveLocations -> String -> String
$cshow :: DirectiveLocations -> String
show :: DirectiveLocations -> String
$cshowList :: [DirectiveLocations] -> String -> String
showList :: [DirectiveLocations] -> String -> String
Show)
_DirectiveLocations :: Name
_DirectiveLocations = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.DirectiveLocations")
_DirectiveLocations_sequence :: Name
_DirectiveLocations_sequence = (String -> Name
Core.Name String
"sequence")
_DirectiveLocations_sequence2 :: Name
_DirectiveLocations_sequence2 = (String -> Name
Core.Name 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
(DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> Bool)
-> (DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> Bool)
-> Eq DirectiveLocations_Sequence
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
== :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
$c/= :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
/= :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
Eq, Eq DirectiveLocations_Sequence
Eq DirectiveLocations_Sequence =>
(DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> Ordering)
-> (DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> Bool)
-> (DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> Bool)
-> (DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> Bool)
-> (DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> Bool)
-> (DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> DirectiveLocations_Sequence)
-> (DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> DirectiveLocations_Sequence)
-> Ord 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
$ccompare :: DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> Ordering
compare :: DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> Ordering
$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
>= :: DirectiveLocations_Sequence -> DirectiveLocations_Sequence -> Bool
$cmax :: DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> DirectiveLocations_Sequence
max :: DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> DirectiveLocations_Sequence
$cmin :: DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> DirectiveLocations_Sequence
min :: DirectiveLocations_Sequence
-> DirectiveLocations_Sequence -> DirectiveLocations_Sequence
Ord, ReadPrec [DirectiveLocations_Sequence]
ReadPrec DirectiveLocations_Sequence
Int -> ReadS DirectiveLocations_Sequence
ReadS [DirectiveLocations_Sequence]
(Int -> ReadS DirectiveLocations_Sequence)
-> ReadS [DirectiveLocations_Sequence]
-> ReadPrec DirectiveLocations_Sequence
-> ReadPrec [DirectiveLocations_Sequence]
-> Read DirectiveLocations_Sequence
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DirectiveLocations_Sequence
readsPrec :: Int -> ReadS DirectiveLocations_Sequence
$creadList :: ReadS [DirectiveLocations_Sequence]
readList :: ReadS [DirectiveLocations_Sequence]
$creadPrec :: ReadPrec DirectiveLocations_Sequence
readPrec :: ReadPrec DirectiveLocations_Sequence
$creadListPrec :: ReadPrec [DirectiveLocations_Sequence]
readListPrec :: ReadPrec [DirectiveLocations_Sequence]
Read, Int -> DirectiveLocations_Sequence -> String -> String
[DirectiveLocations_Sequence] -> String -> String
DirectiveLocations_Sequence -> String
(Int -> DirectiveLocations_Sequence -> String -> String)
-> (DirectiveLocations_Sequence -> String)
-> ([DirectiveLocations_Sequence] -> String -> String)
-> Show DirectiveLocations_Sequence
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> DirectiveLocations_Sequence -> String -> String
showsPrec :: Int -> DirectiveLocations_Sequence -> String -> String
$cshow :: DirectiveLocations_Sequence -> String
show :: DirectiveLocations_Sequence -> String
$cshowList :: [DirectiveLocations_Sequence] -> String -> String
showList :: [DirectiveLocations_Sequence] -> String -> String
Show)
_DirectiveLocations_Sequence :: Name
_DirectiveLocations_Sequence = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.DirectiveLocations.Sequence")
_DirectiveLocations_Sequence_directiveLocations :: Name
_DirectiveLocations_Sequence_directiveLocations = (String -> Name
Core.Name String
"directiveLocations")
_DirectiveLocations_Sequence_directiveLocation :: Name
_DirectiveLocations_Sequence_directiveLocation = (String -> Name
Core.Name 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
(DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool)
-> (DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool)
-> Eq DirectiveLocations_Sequence2
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
== :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
$c/= :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
/= :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
Eq, Eq DirectiveLocations_Sequence2
Eq DirectiveLocations_Sequence2 =>
(DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Ordering)
-> (DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool)
-> (DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool)
-> (DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool)
-> (DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool)
-> (DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> DirectiveLocations_Sequence2)
-> (DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> DirectiveLocations_Sequence2)
-> Ord 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
$ccompare :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Ordering
compare :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Ordering
$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
>= :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> Bool
$cmax :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> DirectiveLocations_Sequence2
max :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> DirectiveLocations_Sequence2
$cmin :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> DirectiveLocations_Sequence2
min :: DirectiveLocations_Sequence2
-> DirectiveLocations_Sequence2 -> DirectiveLocations_Sequence2
Ord, ReadPrec [DirectiveLocations_Sequence2]
ReadPrec DirectiveLocations_Sequence2
Int -> ReadS DirectiveLocations_Sequence2
ReadS [DirectiveLocations_Sequence2]
(Int -> ReadS DirectiveLocations_Sequence2)
-> ReadS [DirectiveLocations_Sequence2]
-> ReadPrec DirectiveLocations_Sequence2
-> ReadPrec [DirectiveLocations_Sequence2]
-> Read DirectiveLocations_Sequence2
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DirectiveLocations_Sequence2
readsPrec :: Int -> ReadS DirectiveLocations_Sequence2
$creadList :: ReadS [DirectiveLocations_Sequence2]
readList :: ReadS [DirectiveLocations_Sequence2]
$creadPrec :: ReadPrec DirectiveLocations_Sequence2
readPrec :: ReadPrec DirectiveLocations_Sequence2
$creadListPrec :: ReadPrec [DirectiveLocations_Sequence2]
readListPrec :: ReadPrec [DirectiveLocations_Sequence2]
Read, Int -> DirectiveLocations_Sequence2 -> String -> String
[DirectiveLocations_Sequence2] -> String -> String
DirectiveLocations_Sequence2 -> String
(Int -> DirectiveLocations_Sequence2 -> String -> String)
-> (DirectiveLocations_Sequence2 -> String)
-> ([DirectiveLocations_Sequence2] -> String -> String)
-> Show DirectiveLocations_Sequence2
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> DirectiveLocations_Sequence2 -> String -> String
showsPrec :: Int -> DirectiveLocations_Sequence2 -> String -> String
$cshow :: DirectiveLocations_Sequence2 -> String
show :: DirectiveLocations_Sequence2 -> String
$cshowList :: [DirectiveLocations_Sequence2] -> String -> String
showList :: [DirectiveLocations_Sequence2] -> String -> String
Show)
_DirectiveLocations_Sequence2 :: Name
_DirectiveLocations_Sequence2 = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.DirectiveLocations.Sequence2")
_DirectiveLocations_Sequence2_or :: Name
_DirectiveLocations_Sequence2_or = (String -> Name
Core.Name String
"or")
_DirectiveLocations_Sequence2_directiveLocation :: Name
_DirectiveLocations_Sequence2_directiveLocation = (String -> Name
Core.Name String
"directiveLocation")
data DirectiveLocation =
DirectiveLocationExecutable ExecutableDirectiveLocation |
DirectiveLocationTypeSystem TypeSystemDirectiveLocation
deriving (DirectiveLocation -> DirectiveLocation -> Bool
(DirectiveLocation -> DirectiveLocation -> Bool)
-> (DirectiveLocation -> DirectiveLocation -> Bool)
-> Eq DirectiveLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DirectiveLocation -> DirectiveLocation -> Bool
== :: DirectiveLocation -> DirectiveLocation -> Bool
$c/= :: DirectiveLocation -> DirectiveLocation -> Bool
/= :: DirectiveLocation -> DirectiveLocation -> Bool
Eq, Eq DirectiveLocation
Eq DirectiveLocation =>
(DirectiveLocation -> DirectiveLocation -> Ordering)
-> (DirectiveLocation -> DirectiveLocation -> Bool)
-> (DirectiveLocation -> DirectiveLocation -> Bool)
-> (DirectiveLocation -> DirectiveLocation -> Bool)
-> (DirectiveLocation -> DirectiveLocation -> Bool)
-> (DirectiveLocation -> DirectiveLocation -> DirectiveLocation)
-> (DirectiveLocation -> DirectiveLocation -> DirectiveLocation)
-> Ord 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
$ccompare :: DirectiveLocation -> DirectiveLocation -> Ordering
compare :: DirectiveLocation -> DirectiveLocation -> Ordering
$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
>= :: DirectiveLocation -> DirectiveLocation -> Bool
$cmax :: DirectiveLocation -> DirectiveLocation -> DirectiveLocation
max :: DirectiveLocation -> DirectiveLocation -> DirectiveLocation
$cmin :: DirectiveLocation -> DirectiveLocation -> DirectiveLocation
min :: DirectiveLocation -> DirectiveLocation -> DirectiveLocation
Ord, ReadPrec [DirectiveLocation]
ReadPrec DirectiveLocation
Int -> ReadS DirectiveLocation
ReadS [DirectiveLocation]
(Int -> ReadS DirectiveLocation)
-> ReadS [DirectiveLocation]
-> ReadPrec DirectiveLocation
-> ReadPrec [DirectiveLocation]
-> Read DirectiveLocation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS DirectiveLocation
readsPrec :: Int -> ReadS DirectiveLocation
$creadList :: ReadS [DirectiveLocation]
readList :: ReadS [DirectiveLocation]
$creadPrec :: ReadPrec DirectiveLocation
readPrec :: ReadPrec DirectiveLocation
$creadListPrec :: ReadPrec [DirectiveLocation]
readListPrec :: ReadPrec [DirectiveLocation]
Read, Int -> DirectiveLocation -> String -> String
[DirectiveLocation] -> String -> String
DirectiveLocation -> String
(Int -> DirectiveLocation -> String -> String)
-> (DirectiveLocation -> String)
-> ([DirectiveLocation] -> String -> String)
-> Show DirectiveLocation
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> DirectiveLocation -> String -> String
showsPrec :: Int -> DirectiveLocation -> String -> String
$cshow :: DirectiveLocation -> String
show :: DirectiveLocation -> String
$cshowList :: [DirectiveLocation] -> String -> String
showList :: [DirectiveLocation] -> String -> String
Show)
_DirectiveLocation :: Name
_DirectiveLocation = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.DirectiveLocation")
_DirectiveLocation_executable :: Name
_DirectiveLocation_executable = (String -> Name
Core.Name String
"executable")
_DirectiveLocation_typeSystem :: Name
_DirectiveLocation_typeSystem = (String -> Name
Core.Name String
"typeSystem")
data ExecutableDirectiveLocation =
ExecutableDirectiveLocationQUERY |
ExecutableDirectiveLocationMUTATION |
ExecutableDirectiveLocationSUBSCRIPTION |
ExecutableDirectiveLocationFIELD |
ExecutableDirectiveLocationFRAGMENTLowbarDEFINITION |
ExecutableDirectiveLocationFRAGMENTLowbarSPREAD |
ExecutableDirectiveLocationINLINELowbarFRAGMENT |
ExecutableDirectiveLocationVARIABLELowbarDEFINITION
deriving (ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
(ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Bool)
-> (ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Bool)
-> Eq ExecutableDirectiveLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
== :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
$c/= :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
/= :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
Eq, Eq ExecutableDirectiveLocation
Eq ExecutableDirectiveLocation =>
(ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Ordering)
-> (ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Bool)
-> (ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Bool)
-> (ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Bool)
-> (ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Bool)
-> (ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> ExecutableDirectiveLocation)
-> (ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> ExecutableDirectiveLocation)
-> Ord 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
$ccompare :: ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Ordering
compare :: ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> Ordering
$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
>= :: ExecutableDirectiveLocation -> ExecutableDirectiveLocation -> Bool
$cmax :: ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> ExecutableDirectiveLocation
max :: ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> ExecutableDirectiveLocation
$cmin :: ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> ExecutableDirectiveLocation
min :: ExecutableDirectiveLocation
-> ExecutableDirectiveLocation -> ExecutableDirectiveLocation
Ord, ReadPrec [ExecutableDirectiveLocation]
ReadPrec ExecutableDirectiveLocation
Int -> ReadS ExecutableDirectiveLocation
ReadS [ExecutableDirectiveLocation]
(Int -> ReadS ExecutableDirectiveLocation)
-> ReadS [ExecutableDirectiveLocation]
-> ReadPrec ExecutableDirectiveLocation
-> ReadPrec [ExecutableDirectiveLocation]
-> Read ExecutableDirectiveLocation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS ExecutableDirectiveLocation
readsPrec :: Int -> ReadS ExecutableDirectiveLocation
$creadList :: ReadS [ExecutableDirectiveLocation]
readList :: ReadS [ExecutableDirectiveLocation]
$creadPrec :: ReadPrec ExecutableDirectiveLocation
readPrec :: ReadPrec ExecutableDirectiveLocation
$creadListPrec :: ReadPrec [ExecutableDirectiveLocation]
readListPrec :: ReadPrec [ExecutableDirectiveLocation]
Read, Int -> ExecutableDirectiveLocation -> String -> String
[ExecutableDirectiveLocation] -> String -> String
ExecutableDirectiveLocation -> String
(Int -> ExecutableDirectiveLocation -> String -> String)
-> (ExecutableDirectiveLocation -> String)
-> ([ExecutableDirectiveLocation] -> String -> String)
-> Show ExecutableDirectiveLocation
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> ExecutableDirectiveLocation -> String -> String
showsPrec :: Int -> ExecutableDirectiveLocation -> String -> String
$cshow :: ExecutableDirectiveLocation -> String
show :: ExecutableDirectiveLocation -> String
$cshowList :: [ExecutableDirectiveLocation] -> String -> String
showList :: [ExecutableDirectiveLocation] -> String -> String
Show)
_ExecutableDirectiveLocation :: Name
_ExecutableDirectiveLocation = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.ExecutableDirectiveLocation")
_ExecutableDirectiveLocation_qUERY :: Name
_ExecutableDirectiveLocation_qUERY = (String -> Name
Core.Name String
"qUERY")
_ExecutableDirectiveLocation_mUTATION :: Name
_ExecutableDirectiveLocation_mUTATION = (String -> Name
Core.Name String
"mUTATION")
_ExecutableDirectiveLocation_sUBSCRIPTION :: Name
_ExecutableDirectiveLocation_sUBSCRIPTION = (String -> Name
Core.Name String
"sUBSCRIPTION")
_ExecutableDirectiveLocation_fIELD :: Name
_ExecutableDirectiveLocation_fIELD = (String -> Name
Core.Name String
"fIELD")
_ExecutableDirectiveLocation_fRAGMENTLowbarDEFINITION :: Name
_ExecutableDirectiveLocation_fRAGMENTLowbarDEFINITION = (String -> Name
Core.Name String
"fRAGMENTLowbarDEFINITION")
_ExecutableDirectiveLocation_fRAGMENTLowbarSPREAD :: Name
_ExecutableDirectiveLocation_fRAGMENTLowbarSPREAD = (String -> Name
Core.Name String
"fRAGMENTLowbarSPREAD")
_ExecutableDirectiveLocation_iNLINELowbarFRAGMENT :: Name
_ExecutableDirectiveLocation_iNLINELowbarFRAGMENT = (String -> Name
Core.Name String
"iNLINELowbarFRAGMENT")
_ExecutableDirectiveLocation_vARIABLELowbarDEFINITION :: Name
_ExecutableDirectiveLocation_vARIABLELowbarDEFINITION = (String -> Name
Core.Name String
"vARIABLELowbarDEFINITION")
data TypeSystemDirectiveLocation =
TypeSystemDirectiveLocationSCHEMA |
TypeSystemDirectiveLocationSCALAR |
TypeSystemDirectiveLocationOBJECT |
TypeSystemDirectiveLocationFIELDLowbarDEFINITION |
TypeSystemDirectiveLocationARGUMENTLowbarDEFINITION |
TypeSystemDirectiveLocationINTERFACE |
TypeSystemDirectiveLocationUNION |
TypeSystemDirectiveLocationENUM |
TypeSystemDirectiveLocationENUMLowbarVALUE |
TypeSystemDirectiveLocationINPUTLowbarOBJECT |
TypeSystemDirectiveLocationINPUTLowbarFIELDLowbarDEFINITION
deriving (TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
(TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Bool)
-> (TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Bool)
-> Eq TypeSystemDirectiveLocation
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
== :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
$c/= :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
/= :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
Eq, Eq TypeSystemDirectiveLocation
Eq TypeSystemDirectiveLocation =>
(TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Ordering)
-> (TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Bool)
-> (TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Bool)
-> (TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Bool)
-> (TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Bool)
-> (TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation)
-> (TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation)
-> Ord 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
$ccompare :: TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Ordering
compare :: TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> Ordering
$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
>= :: TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation -> Bool
$cmax :: TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation
max :: TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation
$cmin :: TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation
min :: TypeSystemDirectiveLocation
-> TypeSystemDirectiveLocation -> TypeSystemDirectiveLocation
Ord, ReadPrec [TypeSystemDirectiveLocation]
ReadPrec TypeSystemDirectiveLocation
Int -> ReadS TypeSystemDirectiveLocation
ReadS [TypeSystemDirectiveLocation]
(Int -> ReadS TypeSystemDirectiveLocation)
-> ReadS [TypeSystemDirectiveLocation]
-> ReadPrec TypeSystemDirectiveLocation
-> ReadPrec [TypeSystemDirectiveLocation]
-> Read TypeSystemDirectiveLocation
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: Int -> ReadS TypeSystemDirectiveLocation
readsPrec :: Int -> ReadS TypeSystemDirectiveLocation
$creadList :: ReadS [TypeSystemDirectiveLocation]
readList :: ReadS [TypeSystemDirectiveLocation]
$creadPrec :: ReadPrec TypeSystemDirectiveLocation
readPrec :: ReadPrec TypeSystemDirectiveLocation
$creadListPrec :: ReadPrec [TypeSystemDirectiveLocation]
readListPrec :: ReadPrec [TypeSystemDirectiveLocation]
Read, Int -> TypeSystemDirectiveLocation -> String -> String
[TypeSystemDirectiveLocation] -> String -> String
TypeSystemDirectiveLocation -> String
(Int -> TypeSystemDirectiveLocation -> String -> String)
-> (TypeSystemDirectiveLocation -> String)
-> ([TypeSystemDirectiveLocation] -> String -> String)
-> Show TypeSystemDirectiveLocation
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
$cshowsPrec :: Int -> TypeSystemDirectiveLocation -> String -> String
showsPrec :: Int -> TypeSystemDirectiveLocation -> String -> String
$cshow :: TypeSystemDirectiveLocation -> String
show :: TypeSystemDirectiveLocation -> String
$cshowList :: [TypeSystemDirectiveLocation] -> String -> String
showList :: [TypeSystemDirectiveLocation] -> String -> String
Show)
_TypeSystemDirectiveLocation :: Name
_TypeSystemDirectiveLocation = (String -> Name
Core.Name String
"hydra/langs/graphql/syntax.TypeSystemDirectiveLocation")
_TypeSystemDirectiveLocation_sCHEMA :: Name
_TypeSystemDirectiveLocation_sCHEMA = (String -> Name
Core.Name String
"sCHEMA")
_TypeSystemDirectiveLocation_sCALAR :: Name
_TypeSystemDirectiveLocation_sCALAR = (String -> Name
Core.Name String
"sCALAR")
_TypeSystemDirectiveLocation_oBJECT :: Name
_TypeSystemDirectiveLocation_oBJECT = (String -> Name
Core.Name String
"oBJECT")
_TypeSystemDirectiveLocation_fIELDLowbarDEFINITION :: Name
_TypeSystemDirectiveLocation_fIELDLowbarDEFINITION = (String -> Name
Core.Name String
"fIELDLowbarDEFINITION")
_TypeSystemDirectiveLocation_aRGUMENTLowbarDEFINITION :: Name
_TypeSystemDirectiveLocation_aRGUMENTLowbarDEFINITION = (String -> Name
Core.Name String
"aRGUMENTLowbarDEFINITION")
_TypeSystemDirectiveLocation_iNTERFACE :: Name
_TypeSystemDirectiveLocation_iNTERFACE = (String -> Name
Core.Name String
"iNTERFACE")
_TypeSystemDirectiveLocation_uNION :: Name
_TypeSystemDirectiveLocation_uNION = (String -> Name
Core.Name String
"uNION")
_TypeSystemDirectiveLocation_eNUM :: Name
_TypeSystemDirectiveLocation_eNUM = (String -> Name
Core.Name String
"eNUM")
_TypeSystemDirectiveLocation_eNUMLowbarVALUE :: Name
_TypeSystemDirectiveLocation_eNUMLowbarVALUE = (String -> Name
Core.Name String
"eNUMLowbarVALUE")
_TypeSystemDirectiveLocation_iNPUTLowbarOBJECT :: Name
_TypeSystemDirectiveLocation_iNPUTLowbarOBJECT = (String -> Name
Core.Name String
"iNPUTLowbarOBJECT")
_TypeSystemDirectiveLocation_iNPUTLowbarFIELDLowbarDEFINITION :: Name
_TypeSystemDirectiveLocation_iNPUTLowbarFIELDLowbarDEFINITION = (String -> Name
Core.Name String
"iNPUTLowbarFIELDLowbarDEFINITION")