Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
This module defines an abstract syntax tree for the GraphQL
language. It
follows closely the structure given in the specification. Please refer to
Facebook's GraphQL Specification.
for more information.
Synopsis
- data Argument = Argument Name (Node Value) Location
- newtype ArgumentsDefinition = ArgumentsDefinition [InputValueDefinition]
- data ConstValue
- data Definition
- newtype Description = Description (Maybe Text)
- data Directive = Directive Name [Argument] Location
- type Document = NonEmpty Definition
- data EnumValueDefinition = EnumValueDefinition Description Name [Directive]
- data ExecutableDefinition
- data Field = Field (Maybe Name) Name [Argument] [Directive] SelectionSetOpt Location
- data FieldDefinition = FieldDefinition Description Name ArgumentsDefinition Type [Directive]
- data FragmentDefinition = FragmentDefinition Name TypeCondition [Directive] SelectionSet Location
- data FragmentSpread = FragmentSpread Name [Directive] Location
- newtype ImplementsInterfaces t = ImplementsInterfaces (t NamedType)
- data InlineFragment = InlineFragment (Maybe TypeCondition) [Directive] SelectionSet Location
- data InputValueDefinition = InputValueDefinition Description Name Type (Maybe (Node ConstValue)) [Directive]
- data Location = Location {}
- type Name = Text
- type NamedType = Name
- data Node a = Node {}
- data NonNullType
- data ObjectField a = ObjectField {}
- data OperationDefinition
- data OperationType
- data OperationTypeDefinition = OperationTypeDefinition OperationType NamedType
- data SchemaExtension
- data Selection
- type SelectionSet = NonEmpty Selection
- type SelectionSetOpt = [Selection]
- data Type
- type TypeCondition = Name
- data TypeDefinition
- = ScalarTypeDefinition Description Name [Directive]
- | ObjectTypeDefinition Description Name (ImplementsInterfaces []) [Directive] [FieldDefinition]
- | InterfaceTypeDefinition Description Name [Directive] [FieldDefinition]
- | UnionTypeDefinition Description Name [Directive] (UnionMemberTypes [])
- | EnumTypeDefinition Description Name [Directive] [EnumValueDefinition]
- | InputObjectTypeDefinition Description Name [Directive] [InputValueDefinition]
- data TypeExtension
- = ScalarTypeExtension Name (NonEmpty Directive)
- | ObjectTypeFieldsDefinitionExtension Name (ImplementsInterfaces []) [Directive] (NonEmpty FieldDefinition)
- | ObjectTypeDirectivesExtension Name (ImplementsInterfaces []) (NonEmpty Directive)
- | ObjectTypeImplementsInterfacesExtension Name (ImplementsInterfaces NonEmpty)
- | InterfaceTypeFieldsDefinitionExtension Name [Directive] (NonEmpty FieldDefinition)
- | InterfaceTypeDirectivesExtension Name (NonEmpty Directive)
- | UnionTypeUnionMemberTypesExtension Name [Directive] (UnionMemberTypes NonEmpty)
- | UnionTypeDirectivesExtension Name (NonEmpty Directive)
- | EnumTypeEnumValuesDefinitionExtension Name [Directive] (NonEmpty EnumValueDefinition)
- | EnumTypeDirectivesExtension Name (NonEmpty Directive)
- | InputObjectTypeInputFieldsDefinitionExtension Name [Directive] (NonEmpty InputValueDefinition)
- | InputObjectTypeDirectivesExtension Name (NonEmpty Directive)
- data TypeSystemDefinition
- data TypeSystemExtension
- newtype UnionMemberTypes t = UnionMemberTypes (t NamedType)
- data Value
- data VariableDefinition = VariableDefinition Name Type (Maybe (Node ConstValue)) Location
- escape :: Char -> String
Documentation
Single argument.
{ user(id: 4) { name } }
Here "id" is an argument for the field "user" and its value is 4.
newtype ArgumentsDefinition Source #
A list of values passed to a field.
type Person { name: String picture(width: Int, height: Int): Url }
Person has two fields, "name" and "picture". "name" doesn't have any
arguments, so ArgumentsDefinition
contains an empty list. "picture"
contains definitions for 2 arguments: "width" and "height".
Instances
Eq ArgumentsDefinition Source # | |
Defined in Language.GraphQL.AST.Document (==) :: ArgumentsDefinition -> ArgumentsDefinition -> Bool # (/=) :: ArgumentsDefinition -> ArgumentsDefinition -> Bool # | |
Show ArgumentsDefinition Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> ArgumentsDefinition -> ShowS # show :: ArgumentsDefinition -> String # showList :: [ArgumentsDefinition] -> ShowS # | |
Semigroup ArgumentsDefinition Source # | |
Defined in Language.GraphQL.AST.Document (<>) :: ArgumentsDefinition -> ArgumentsDefinition -> ArgumentsDefinition # sconcat :: NonEmpty ArgumentsDefinition -> ArgumentsDefinition # stimes :: Integral b => b -> ArgumentsDefinition -> ArgumentsDefinition # | |
Monoid ArgumentsDefinition Source # | |
data ConstValue Source #
Constant input value.
ConstInt Int32 | |
ConstFloat Double | |
ConstString Text | |
ConstBoolean Bool | |
ConstNull | |
ConstEnum Name | |
ConstList [Node ConstValue] | |
ConstObject [ObjectField ConstValue] |
Instances
Eq ConstValue Source # | |
Defined in Language.GraphQL.AST.Document (==) :: ConstValue -> ConstValue -> Bool # (/=) :: ConstValue -> ConstValue -> Bool # | |
Show ConstValue Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> ConstValue -> ShowS # show :: ConstValue -> String # showList :: [ConstValue] -> ShowS # |
data Definition Source #
All kinds of definitions that can occur in a GraphQL document.
ExecutableDefinition ExecutableDefinition | |
TypeSystemDefinition TypeSystemDefinition Location | |
TypeSystemExtension TypeSystemExtension Location |
Instances
Eq Definition Source # | |
Defined in Language.GraphQL.AST.Document (==) :: Definition -> Definition -> Bool # (/=) :: Definition -> Definition -> Bool # | |
Show Definition Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> Definition -> ShowS # show :: Definition -> String # showList :: [Definition] -> ShowS # |
newtype Description Source #
GraphQL has built-in capability to document service APIs. Documentation is a GraphQL string that precedes a particular definition and contains Markdown. Any GraphQL definition can be documented this way.
""" Supported languages. """ enum Language { English EN Russian RU }
Instances
Eq Description Source # | |
Defined in Language.GraphQL.AST.Document (==) :: Description -> Description -> Bool # (/=) :: Description -> Description -> Bool # | |
Show Description Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> Description -> ShowS # show :: Description -> String # showList :: [Description] -> ShowS # |
Directive.
Directives begin with "@", can accept arguments, and can be applied to the most GraphQL elements, providing additional information.
type Document = NonEmpty Definition Source #
GraphQL document.
data EnumValueDefinition Source #
Single value in an enum definition.
enum Direction { NORTH EAST SOUTH WEST }
"NORTH, EAST, SOUTH, and WEST are value definitions of an enum type definition Direction.
Instances
Eq EnumValueDefinition Source # | |
Defined in Language.GraphQL.AST.Document (==) :: EnumValueDefinition -> EnumValueDefinition -> Bool # (/=) :: EnumValueDefinition -> EnumValueDefinition -> Bool # | |
Show EnumValueDefinition Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> EnumValueDefinition -> ShowS # show :: EnumValueDefinition -> String # showList :: [EnumValueDefinition] -> ShowS # |
data ExecutableDefinition Source #
Top-level definition of a document, either an operation or a fragment.
Instances
Eq ExecutableDefinition Source # | |
Defined in Language.GraphQL.AST.Document (==) :: ExecutableDefinition -> ExecutableDefinition -> Bool # (/=) :: ExecutableDefinition -> ExecutableDefinition -> Bool # | |
Show ExecutableDefinition Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> ExecutableDefinition -> ShowS # show :: ExecutableDefinition -> String # showList :: [ExecutableDefinition] -> ShowS # |
The only required property of a field is its name. Optionally it can also have an alias, arguments, directives and a list of subfields.
In the following query "user" is a field with two subfields, "id" and "name":
{ user { id name } }
data FieldDefinition Source #
Definition of a single field in a type.
type Person { name: String picture(width: Int, height: Int): Url }
"name" and "picture", including their arguments and types, are field definitions.
Instances
Eq FieldDefinition Source # | |
Defined in Language.GraphQL.AST.Document (==) :: FieldDefinition -> FieldDefinition -> Bool # (/=) :: FieldDefinition -> FieldDefinition -> Bool # | |
Show FieldDefinition Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> FieldDefinition -> ShowS # show :: FieldDefinition -> String # showList :: [FieldDefinition] -> ShowS # |
data FragmentDefinition Source #
Fragment definition.
Instances
Eq FragmentDefinition Source # | |
Defined in Language.GraphQL.AST.Document (==) :: FragmentDefinition -> FragmentDefinition -> Bool # (/=) :: FragmentDefinition -> FragmentDefinition -> Bool # | |
Show FragmentDefinition Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> FragmentDefinition -> ShowS # show :: FragmentDefinition -> String # showList :: [FragmentDefinition] -> ShowS # |
data FragmentSpread Source #
A fragment spread refers to a fragment defined outside the operation and is expanded at the execution time.
{ user { ...userFragment } } fragment userFragment on UserType { id name }
Instances
Eq FragmentSpread Source # | |
Defined in Language.GraphQL.AST.Document (==) :: FragmentSpread -> FragmentSpread -> Bool # (/=) :: FragmentSpread -> FragmentSpread -> Bool # | |
Show FragmentSpread Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> FragmentSpread -> ShowS # show :: FragmentSpread -> String # showList :: [FragmentSpread] -> ShowS # |
newtype ImplementsInterfaces t Source #
Defines a list of interfaces implemented by the given object type.
type Business implements NamedEntity & ValuedEntity { name: String }
Here the object type Business implements two interfaces: NamedEntity and ValuedEntity.
Instances
Foldable t => Eq (ImplementsInterfaces t) Source # | |
Defined in Language.GraphQL.AST.Document (==) :: ImplementsInterfaces t -> ImplementsInterfaces t -> Bool # (/=) :: ImplementsInterfaces t -> ImplementsInterfaces t -> Bool # | |
Foldable t => Show (ImplementsInterfaces t) Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> ImplementsInterfaces t -> ShowS # show :: ImplementsInterfaces t -> String # showList :: [ImplementsInterfaces t] -> ShowS # |
data InlineFragment Source #
Inline fragments don't have any name and the type condition ("on UserType") is optional.
{ user { ... on UserType { id name } }
Instances
Eq InlineFragment Source # | |
Defined in Language.GraphQL.AST.Document (==) :: InlineFragment -> InlineFragment -> Bool # (/=) :: InlineFragment -> InlineFragment -> Bool # | |
Show InlineFragment Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> InlineFragment -> ShowS # show :: InlineFragment -> String # showList :: [InlineFragment] -> ShowS # |
data InputValueDefinition Source #
Defines an input value.
- Input values can define field arguments, see
ArgumentsDefinition
. - They can also be used as field definitions in an input type.
input Point2D { x: Float y: Float }
The input type Point2D contains two value definitions: "x" and "y".
Instances
Eq InputValueDefinition Source # | |
Defined in Language.GraphQL.AST.Document (==) :: InputValueDefinition -> InputValueDefinition -> Bool # (/=) :: InputValueDefinition -> InputValueDefinition -> Bool # | |
Show InputValueDefinition Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> InputValueDefinition -> ShowS # show :: InputValueDefinition -> String # showList :: [InputValueDefinition] -> ShowS # |
Error location, line and column.
Contains some tree node with a location.
data NonNullType Source #
Helper type to represent Non-Null types and lists of such types.
Instances
Eq NonNullType Source # | |
Defined in Language.GraphQL.AST.Document (==) :: NonNullType -> NonNullType -> Bool # (/=) :: NonNullType -> NonNullType -> Bool # | |
Show NonNullType Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> NonNullType -> ShowS # show :: NonNullType -> String # showList :: [NonNullType] -> ShowS # |
data ObjectField a Source #
Key-value pair.
A list of ObjectField
s represents a GraphQL object type.
Instances
Functor ObjectField Source # | |
Defined in Language.GraphQL.AST.Document fmap :: (a -> b) -> ObjectField a -> ObjectField b # (<$) :: a -> ObjectField b -> ObjectField a # | |
Eq a => Eq (ObjectField a) Source # | |
Defined in Language.GraphQL.AST.Document (==) :: ObjectField a -> ObjectField a -> Bool # (/=) :: ObjectField a -> ObjectField a -> Bool # | |
Show a => Show (ObjectField a) Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> ObjectField a -> ShowS # show :: ObjectField a -> String # showList :: [ObjectField a] -> ShowS # |
data OperationDefinition Source #
Operation definition.
SelectionSet SelectionSet Location | |
OperationDefinition OperationType (Maybe Name) [VariableDefinition] [Directive] SelectionSet Location |
Instances
Eq OperationDefinition Source # | |
Defined in Language.GraphQL.AST.Document (==) :: OperationDefinition -> OperationDefinition -> Bool # (/=) :: OperationDefinition -> OperationDefinition -> Bool # | |
Show OperationDefinition Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> OperationDefinition -> ShowS # show :: OperationDefinition -> String # showList :: [OperationDefinition] -> ShowS # |
data OperationType Source #
GraphQL has 3 operation types:
- query - a read-only fetch.
- mutation - a write operation followed by a fetch.
- subscription - a long-lived request that fetches data in response to source events.
Instances
Eq OperationType Source # | |
Defined in Language.GraphQL.AST.Document (==) :: OperationType -> OperationType -> Bool # (/=) :: OperationType -> OperationType -> Bool # | |
Show OperationType Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> OperationType -> ShowS # show :: OperationType -> String # showList :: [OperationType] -> ShowS # |
data OperationTypeDefinition Source #
Root operation type definition.
Defining root operation types is not required since they have defaults. So the default query root type is Query, and the default mutation root type is Mutation. But these defaults can be changed for a specific schema. In the following code the query root type is changed to MyQueryRootType, and the mutation root type to MyMutationRootType:
schema { query: MyQueryRootType mutation: MyMutationRootType }
Instances
Eq OperationTypeDefinition Source # | |
Defined in Language.GraphQL.AST.Document | |
Show OperationTypeDefinition Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> OperationTypeDefinition -> ShowS # show :: OperationTypeDefinition -> String # showList :: [OperationTypeDefinition] -> ShowS # |
data SchemaExtension Source #
Extension of the schema definition by further operations or directives.
SchemaOperationExtension [Directive] (NonEmpty OperationTypeDefinition) | |
SchemaDirectivesExtension (NonEmpty Directive) |
Instances
Eq SchemaExtension Source # | |
Defined in Language.GraphQL.AST.Document (==) :: SchemaExtension -> SchemaExtension -> Bool # (/=) :: SchemaExtension -> SchemaExtension -> Bool # | |
Show SchemaExtension Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> SchemaExtension -> ShowS # show :: SchemaExtension -> String # showList :: [SchemaExtension] -> ShowS # |
Selection is a single entry in a selection set. It can be a single Field
,
FragmentSpread
or an InlineFragment
.
type SelectionSet = NonEmpty Selection Source #
"Top-level" selection, selection on an operation or fragment.
type SelectionSetOpt = [Selection] Source #
Field selection.
Type representation.
type TypeCondition = Name Source #
Type condition.
data TypeDefinition Source #
Type definitions describe various user-defined types.
Instances
Eq TypeDefinition Source # | |
Defined in Language.GraphQL.AST.Document (==) :: TypeDefinition -> TypeDefinition -> Bool # (/=) :: TypeDefinition -> TypeDefinition -> Bool # | |
Show TypeDefinition Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> TypeDefinition -> ShowS # show :: TypeDefinition -> String # showList :: [TypeDefinition] -> ShowS # |
data TypeExtension Source #
Extensions for custom, already defined types.
Instances
Eq TypeExtension Source # | |
Defined in Language.GraphQL.AST.Document (==) :: TypeExtension -> TypeExtension -> Bool # (/=) :: TypeExtension -> TypeExtension -> Bool # | |
Show TypeExtension Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> TypeExtension -> ShowS # show :: TypeExtension -> String # showList :: [TypeExtension] -> ShowS # |
data TypeSystemDefinition Source #
Type system can define a schema, a type or a directive.
schema {
query: Query
}
directive example on FIELD_DEFINITION
type Query {
field: String
example
}
This example defines a custom directive "@example", which is applied to a field definition of the type definition Query. On the top the schema is defined by taking advantage of the type Query.
SchemaDefinition [Directive] (NonEmpty OperationTypeDefinition) | |
TypeDefinition TypeDefinition | |
DirectiveDefinition Description Name ArgumentsDefinition (NonEmpty DirectiveLocation) |
Instances
Eq TypeSystemDefinition Source # | |
Defined in Language.GraphQL.AST.Document (==) :: TypeSystemDefinition -> TypeSystemDefinition -> Bool # (/=) :: TypeSystemDefinition -> TypeSystemDefinition -> Bool # | |
Show TypeSystemDefinition Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> TypeSystemDefinition -> ShowS # show :: TypeSystemDefinition -> String # showList :: [TypeSystemDefinition] -> ShowS # |
data TypeSystemExtension Source #
Extension for a type system definition. Only schema and type definitions can be extended.
Instances
Eq TypeSystemExtension Source # | |
Defined in Language.GraphQL.AST.Document (==) :: TypeSystemExtension -> TypeSystemExtension -> Bool # (/=) :: TypeSystemExtension -> TypeSystemExtension -> Bool # | |
Show TypeSystemExtension Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> TypeSystemExtension -> ShowS # show :: TypeSystemExtension -> String # showList :: [TypeSystemExtension] -> ShowS # |
newtype UnionMemberTypes t Source #
List of types forming a union.
union SearchResult = Person | Photo
Person and Photo are member types of the union SearchResult.
Instances
Foldable t => Eq (UnionMemberTypes t) Source # | |
Defined in Language.GraphQL.AST.Document (==) :: UnionMemberTypes t -> UnionMemberTypes t -> Bool # (/=) :: UnionMemberTypes t -> UnionMemberTypes t -> Bool # | |
Foldable t => Show (UnionMemberTypes t) Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> UnionMemberTypes t -> ShowS # show :: UnionMemberTypes t -> String # showList :: [UnionMemberTypes t] -> ShowS # |
Input value (literal or variable).
data VariableDefinition Source #
Variable definition.
Each operation can include a list of variables:
query (protagonist: String = "Zarathustra") { getAuthor(protagonist: $protagonist) }
This query defines an optional variable protagonist
of type String
,
its default value is "Zarathustra". If no default value is defined and no
value is provided, a variable can still be null
if its type is nullable.
Variables are usually passed along with the query, but not in the query itself. They make queries reusable.
Instances
Eq VariableDefinition Source # | |
Defined in Language.GraphQL.AST.Document (==) :: VariableDefinition -> VariableDefinition -> Bool # (/=) :: VariableDefinition -> VariableDefinition -> Bool # | |
Show VariableDefinition Source # | |
Defined in Language.GraphQL.AST.Document showsPrec :: Int -> VariableDefinition -> ShowS # show :: VariableDefinition -> String # showList :: [VariableDefinition] -> ShowS # |