| Safe Haskell | Safe | 
|---|---|
| Language | Haskell2010 | 
Language.GraphQL.AST.Document
Description
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 List) [Directive] [FieldDefinition]
- | InterfaceTypeDefinition Description Name [Directive] [FieldDefinition]
- | UnionTypeDefinition Description Name [Directive] (UnionMemberTypes List)
- | EnumTypeDefinition Description Name [Directive] [EnumValueDefinition]
- | InputObjectTypeDefinition Description Name [Directive] [InputValueDefinition]
 
- data TypeExtension- = ScalarTypeExtension Name (NonEmpty Directive)
- | ObjectTypeFieldsDefinitionExtension Name (ImplementsInterfaces List) [Directive] (NonEmpty FieldDefinition)
- | ObjectTypeDirectivesExtension Name (ImplementsInterfaces List) (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
- showVariableName :: VariableDefinition -> String
- showVariable :: VariableDefinition -> 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".
Constructors
| ArgumentsDefinition [InputValueDefinition] | 
Instances
| Monoid ArgumentsDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods mempty :: ArgumentsDefinition # mappend :: ArgumentsDefinition -> ArgumentsDefinition -> ArgumentsDefinition # | |
| Semigroup ArgumentsDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods (<>) :: ArgumentsDefinition -> ArgumentsDefinition -> ArgumentsDefinition # sconcat :: NonEmpty ArgumentsDefinition -> ArgumentsDefinition # stimes :: Integral b => b -> ArgumentsDefinition -> ArgumentsDefinition # | |
| Show ArgumentsDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> ArgumentsDefinition -> ShowS # show :: ArgumentsDefinition -> String # showList :: [ArgumentsDefinition] -> ShowS # | |
| Eq ArgumentsDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: ArgumentsDefinition -> ArgumentsDefinition -> Bool # (/=) :: ArgumentsDefinition -> ArgumentsDefinition -> Bool # | |
data ConstValue Source #
Constant input value.
Constructors
| ConstInt Int32 | |
| ConstFloat Double | |
| ConstString Text | |
| ConstBoolean Bool | |
| ConstNull | |
| ConstEnum Name | |
| ConstList [Node ConstValue] | |
| ConstObject [ObjectField ConstValue] | 
Instances
| Show ConstValue Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> ConstValue -> ShowS # show :: ConstValue -> String # showList :: [ConstValue] -> ShowS # | |
| Eq ConstValue Source # | |
| Defined in Language.GraphQL.AST.Document | |
data Definition Source #
All kinds of definitions that can occur in a GraphQL document.
Constructors
| ExecutableDefinition ExecutableDefinition | |
| TypeSystemDefinition TypeSystemDefinition Location | |
| TypeSystemExtension TypeSystemExtension Location | 
Instances
| Show Definition Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> Definition -> ShowS # show :: Definition -> String # showList :: [Definition] -> ShowS # | |
| Eq Definition Source # | |
| Defined in Language.GraphQL.AST.Document | |
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
}
Constructors
| Description (Maybe Text) | 
Instances
| Monoid Description Source # | |
| Defined in Language.GraphQL.AST.Document Methods mempty :: Description # mappend :: Description -> Description -> Description # mconcat :: [Description] -> Description # | |
| Semigroup Description Source # | |
| Defined in Language.GraphQL.AST.Document Methods (<>) :: Description -> Description -> Description # sconcat :: NonEmpty Description -> Description # stimes :: Integral b => b -> Description -> Description # | |
| Show Description Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> Description -> ShowS # show :: Description -> String # showList :: [Description] -> ShowS # | |
| Eq Description Source # | |
| Defined in Language.GraphQL.AST.Document | |
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.
Constructors
| EnumValueDefinition Description Name [Directive] | 
Instances
| Show EnumValueDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> EnumValueDefinition -> ShowS # show :: EnumValueDefinition -> String # showList :: [EnumValueDefinition] -> ShowS # | |
| Eq EnumValueDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: EnumValueDefinition -> EnumValueDefinition -> Bool # (/=) :: EnumValueDefinition -> EnumValueDefinition -> Bool # | |
data ExecutableDefinition Source #
Top-level definition of a document, either an operation or a fragment.
Instances
| Show ExecutableDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> ExecutableDefinition -> ShowS # show :: ExecutableDefinition -> String # showList :: [ExecutableDefinition] -> ShowS # | |
| Eq ExecutableDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: ExecutableDefinition -> ExecutableDefinition -> Bool # (/=) :: ExecutableDefinition -> ExecutableDefinition -> Bool # | |
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
  }
}
Instances
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.
Constructors
| FieldDefinition Description Name ArgumentsDefinition Type [Directive] | 
Instances
| Show FieldDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> FieldDefinition -> ShowS # show :: FieldDefinition -> String # showList :: [FieldDefinition] -> ShowS # | |
| Eq FieldDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: FieldDefinition -> FieldDefinition -> Bool # (/=) :: FieldDefinition -> FieldDefinition -> Bool # | |
data FragmentDefinition Source #
Fragment definition.
Constructors
| FragmentDefinition Name TypeCondition [Directive] SelectionSet Location | 
Instances
| Show FragmentDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> FragmentDefinition -> ShowS # show :: FragmentDefinition -> String # showList :: [FragmentDefinition] -> ShowS # | |
| Eq FragmentDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: FragmentDefinition -> FragmentDefinition -> Bool # (/=) :: FragmentDefinition -> FragmentDefinition -> Bool # | |
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
}
Constructors
| FragmentSpread Name [Directive] Location | 
Instances
| Show FragmentSpread Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> FragmentSpread -> ShowS # show :: FragmentSpread -> String # showList :: [FragmentSpread] -> ShowS # | |
| Eq FragmentSpread Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: FragmentSpread -> FragmentSpread -> Bool # (/=) :: FragmentSpread -> FragmentSpread -> Bool # | |
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.
Constructors
| ImplementsInterfaces (t NamedType) | 
Instances
| Foldable t => Show (ImplementsInterfaces t) Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> ImplementsInterfaces t -> ShowS # show :: ImplementsInterfaces t -> String # showList :: [ImplementsInterfaces t] -> ShowS # | |
| Foldable t => Eq (ImplementsInterfaces t) Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: ImplementsInterfaces t -> ImplementsInterfaces t -> Bool # (/=) :: ImplementsInterfaces t -> ImplementsInterfaces t -> Bool # | |
data InlineFragment Source #
Inline fragments don't have any name and the type condition ("on UserType") is optional.
{
  user {
    ... on UserType {
      id
      name
    }
}
Constructors
| InlineFragment (Maybe TypeCondition) [Directive] SelectionSet Location | 
Instances
| Show InlineFragment Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> InlineFragment -> ShowS # show :: InlineFragment -> String # showList :: [InlineFragment] -> ShowS # | |
| Eq InlineFragment Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: InlineFragment -> InlineFragment -> Bool # (/=) :: InlineFragment -> InlineFragment -> Bool # | |
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".
Constructors
| InputValueDefinition Description Name Type (Maybe (Node ConstValue)) [Directive] | 
Instances
| Show InputValueDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> InputValueDefinition -> ShowS # show :: InputValueDefinition -> String # showList :: [InputValueDefinition] -> ShowS # | |
| Eq InputValueDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: InputValueDefinition -> InputValueDefinition -> Bool # (/=) :: InputValueDefinition -> InputValueDefinition -> Bool # | |
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.
Constructors
| NonNullTypeNamed Name | |
| NonNullTypeList Type | 
Instances
| Show NonNullType Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> NonNullType -> ShowS # show :: NonNullType -> String # showList :: [NonNullType] -> ShowS # | |
| Eq NonNullType Source # | |
| Defined in Language.GraphQL.AST.Document | |
data ObjectField a Source #
Key-value pair.
A list of ObjectFields represents a GraphQL object type.
Instances
| Functor ObjectField Source # | |
| Defined in Language.GraphQL.AST.Document Methods fmap :: (a -> b) -> ObjectField a -> ObjectField b # (<$) :: a -> ObjectField b -> ObjectField a # | |
| Show a => Show (ObjectField a) Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> ObjectField a -> ShowS # show :: ObjectField a -> String # showList :: [ObjectField a] -> ShowS # | |
| Eq a => Eq (ObjectField a) Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: ObjectField a -> ObjectField a -> Bool # (/=) :: ObjectField a -> ObjectField a -> Bool # | |
data OperationDefinition Source #
Operation definition.
Constructors
| SelectionSet SelectionSet Location | |
| OperationDefinition OperationType (Maybe Name) [VariableDefinition] [Directive] SelectionSet Location | 
Instances
| Show OperationDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> OperationDefinition -> ShowS # show :: OperationDefinition -> String # showList :: [OperationDefinition] -> ShowS # | |
| Eq OperationDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: OperationDefinition -> OperationDefinition -> Bool # (/=) :: OperationDefinition -> OperationDefinition -> Bool # | |
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.
Constructors
| Query | |
| Mutation | |
| Subscription | 
Instances
| Show OperationType Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> OperationType -> ShowS # show :: OperationType -> String # showList :: [OperationType] -> ShowS # | |
| Eq OperationType Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: OperationType -> OperationType -> Bool # (/=) :: OperationType -> OperationType -> Bool # | |
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
}
Constructors
| OperationTypeDefinition OperationType NamedType | 
Instances
| Show OperationTypeDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> OperationTypeDefinition -> ShowS # show :: OperationTypeDefinition -> String # showList :: [OperationTypeDefinition] -> ShowS # | |
| Eq OperationTypeDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: OperationTypeDefinition -> OperationTypeDefinition -> Bool # (/=) :: OperationTypeDefinition -> OperationTypeDefinition -> Bool # | |
data SchemaExtension Source #
Extension of the schema definition by further operations or directives.
Constructors
| SchemaOperationExtension [Directive] (NonEmpty OperationTypeDefinition) | |
| SchemaDirectivesExtension (NonEmpty Directive) | 
Instances
| Show SchemaExtension Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> SchemaExtension -> ShowS # show :: SchemaExtension -> String # showList :: [SchemaExtension] -> ShowS # | |
| Eq SchemaExtension Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: SchemaExtension -> SchemaExtension -> Bool # (/=) :: SchemaExtension -> SchemaExtension -> Bool # | |
Selection is a single entry in a selection set. It can be a single Field,
 FragmentSpread or an InlineFragment.
Constructors
| FieldSelection Field | |
| FragmentSpreadSelection FragmentSpread | |
| InlineFragmentSelection InlineFragment | 
type SelectionSet = NonEmpty Selection Source #
"Top-level" selection, selection on an operation or fragment.
type SelectionSetOpt = [Selection] Source #
Field selection.
Type representation.
Constructors
| TypeNamed Name | |
| TypeList Type | |
| TypeNonNull NonNullType | 
type TypeCondition = Name Source #
Type condition.
data TypeDefinition Source #
Type definitions describe various user-defined types.
Constructors
Instances
| Show TypeDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> TypeDefinition -> ShowS # show :: TypeDefinition -> String # showList :: [TypeDefinition] -> ShowS # | |
| Eq TypeDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: TypeDefinition -> TypeDefinition -> Bool # (/=) :: TypeDefinition -> TypeDefinition -> Bool # | |
data TypeExtension Source #
Extensions for custom, already defined types.
Constructors
Instances
| Show TypeExtension Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> TypeExtension -> ShowS # show :: TypeExtension -> String # showList :: [TypeExtension] -> ShowS # | |
| Eq TypeExtension Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: TypeExtension -> TypeExtension -> Bool # (/=) :: TypeExtension -> TypeExtension -> Bool # | |
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.
Constructors
| SchemaDefinition [Directive] (NonEmpty OperationTypeDefinition) | |
| TypeDefinition TypeDefinition | |
| DirectiveDefinition Description Name ArgumentsDefinition (NonEmpty DirectiveLocation) | 
Instances
| Show TypeSystemDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> TypeSystemDefinition -> ShowS # show :: TypeSystemDefinition -> String # showList :: [TypeSystemDefinition] -> ShowS # | |
| Eq TypeSystemDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: TypeSystemDefinition -> TypeSystemDefinition -> Bool # (/=) :: TypeSystemDefinition -> TypeSystemDefinition -> Bool # | |
data TypeSystemExtension Source #
Extension for a type system definition. Only schema and type definitions can be extended.
Constructors
| SchemaExtension SchemaExtension | |
| TypeExtension TypeExtension | 
Instances
| Show TypeSystemExtension Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> TypeSystemExtension -> ShowS # show :: TypeSystemExtension -> String # showList :: [TypeSystemExtension] -> ShowS # | |
| Eq TypeSystemExtension Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: TypeSystemExtension -> TypeSystemExtension -> Bool # (/=) :: TypeSystemExtension -> TypeSystemExtension -> Bool # | |
newtype UnionMemberTypes t Source #
List of types forming a union.
union SearchResult = Person | Photo
Person and Photo are member types of the union SearchResult.
Constructors
| UnionMemberTypes (t NamedType) | 
Instances
| Foldable t => Show (UnionMemberTypes t) Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> UnionMemberTypes t -> ShowS # show :: UnionMemberTypes t -> String # showList :: [UnionMemberTypes t] -> ShowS # | |
| Foldable t => Eq (UnionMemberTypes t) Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: UnionMemberTypes t -> UnionMemberTypes t -> Bool # (/=) :: UnionMemberTypes t -> UnionMemberTypes t -> Bool # | |
Input value (literal or variable).
Constructors
| Variable Name | |
| Int Int32 | |
| Float Double | |
| String Text | |
| Boolean Bool | |
| Null | |
| Enum Name | |
| List [Node Value] | |
| Object [ObjectField Value] | 
Instances
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.
Constructors
| VariableDefinition Name Type (Maybe (Node ConstValue)) Location | 
Instances
| Show VariableDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods showsPrec :: Int -> VariableDefinition -> ShowS # show :: VariableDefinition -> String # showList :: [VariableDefinition] -> ShowS # | |
| Eq VariableDefinition Source # | |
| Defined in Language.GraphQL.AST.Document Methods (==) :: VariableDefinition -> VariableDefinition -> Bool # (/=) :: VariableDefinition -> VariableDefinition -> Bool # | |