2020-01-07 13:56:58 +01:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
2019-12-27 09:14:12 +01:00
|
|
|
-- | This module defines an abstract syntax tree for the @GraphQL@ language. It
|
2019-12-28 07:07:58 +01:00
|
|
|
-- follows closely the structure given in the specification. Please refer to
|
|
|
|
-- <https://facebook.github.io/graphql/ Facebook's GraphQL Specification>.
|
|
|
|
-- for more information.
|
2019-12-26 13:00:47 +01:00
|
|
|
module Language.GraphQL.AST.Document
|
2019-12-28 07:07:58 +01:00
|
|
|
( Alias
|
|
|
|
, Argument(..)
|
2020-01-05 07:42:04 +01:00
|
|
|
, ArgumentsDefinition(..)
|
2020-05-22 10:11:48 +02:00
|
|
|
, ConstValue(..)
|
2020-01-17 12:22:29 +01:00
|
|
|
, Definition(..)
|
2020-01-05 07:42:04 +01:00
|
|
|
, Description(..)
|
2019-12-28 07:07:58 +01:00
|
|
|
, Directive(..)
|
2019-12-26 13:00:47 +01:00
|
|
|
, Document
|
2020-01-12 07:07:04 +01:00
|
|
|
, EnumValueDefinition(..)
|
2019-12-26 13:00:47 +01:00
|
|
|
, ExecutableDefinition(..)
|
2020-01-05 07:42:04 +01:00
|
|
|
, FieldDefinition(..)
|
2019-12-28 07:07:58 +01:00
|
|
|
, FragmentDefinition(..)
|
2020-01-05 07:42:04 +01:00
|
|
|
, ImplementsInterfaces(..)
|
|
|
|
, InputValueDefinition(..)
|
2020-07-08 08:16:14 +02:00
|
|
|
, Location(..)
|
2019-12-28 07:07:58 +01:00
|
|
|
, Name
|
2020-01-07 13:56:58 +01:00
|
|
|
, NamedType
|
2019-12-28 07:07:58 +01:00
|
|
|
, NonNullType(..)
|
|
|
|
, ObjectField(..)
|
|
|
|
, OperationDefinition(..)
|
|
|
|
, OperationType(..)
|
2020-01-03 07:20:48 +01:00
|
|
|
, OperationTypeDefinition(..)
|
2020-01-17 12:22:29 +01:00
|
|
|
, SchemaExtension(..)
|
2019-12-28 07:07:58 +01:00
|
|
|
, Selection(..)
|
|
|
|
, SelectionSet
|
|
|
|
, SelectionSetOpt
|
|
|
|
, Type(..)
|
|
|
|
, TypeCondition
|
2020-01-05 07:42:04 +01:00
|
|
|
, TypeDefinition(..)
|
2020-01-07 13:56:58 +01:00
|
|
|
, TypeExtension(..)
|
2020-01-03 07:20:48 +01:00
|
|
|
, TypeSystemDefinition(..)
|
2020-01-17 12:22:29 +01:00
|
|
|
, TypeSystemExtension(..)
|
2020-01-07 13:56:58 +01:00
|
|
|
, UnionMemberTypes(..)
|
2019-12-28 07:07:58 +01:00
|
|
|
, Value(..)
|
|
|
|
, VariableDefinition(..)
|
2019-12-26 13:00:47 +01:00
|
|
|
) where
|
|
|
|
|
2020-01-07 13:56:58 +01:00
|
|
|
import Data.Foldable (toList)
|
2019-12-28 07:07:58 +01:00
|
|
|
import Data.Int (Int32)
|
2019-12-26 13:00:47 +01:00
|
|
|
import Data.List.NonEmpty (NonEmpty)
|
|
|
|
import Data.Text (Text)
|
2020-01-07 13:56:58 +01:00
|
|
|
import qualified Data.Text as Text
|
2019-12-26 13:00:47 +01:00
|
|
|
import Language.GraphQL.AST.DirectiveLocation
|
|
|
|
|
2019-12-27 09:14:12 +01:00
|
|
|
-- * Language
|
|
|
|
|
2019-12-28 07:07:58 +01:00
|
|
|
-- ** Source Text
|
|
|
|
|
|
|
|
-- | Name.
|
|
|
|
type Name = Text
|
|
|
|
|
2020-07-08 08:16:14 +02:00
|
|
|
-- | Error location, line and column.
|
|
|
|
data Location = Location
|
|
|
|
{ line :: Word
|
|
|
|
, column :: Word
|
|
|
|
} deriving (Eq, Show)
|
|
|
|
|
2019-12-27 09:14:12 +01:00
|
|
|
-- ** Document
|
|
|
|
|
2019-12-26 13:00:47 +01:00
|
|
|
-- | GraphQL document.
|
|
|
|
type Document = NonEmpty Definition
|
|
|
|
|
|
|
|
-- | All kinds of definitions that can occur in a GraphQL document.
|
|
|
|
data Definition
|
|
|
|
= ExecutableDefinition ExecutableDefinition
|
|
|
|
| TypeSystemDefinition TypeSystemDefinition
|
|
|
|
| TypeSystemExtension TypeSystemExtension
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2019-12-28 07:07:58 +01:00
|
|
|
-- | Top-level definition of a document, either an operation or a fragment.
|
|
|
|
data ExecutableDefinition
|
|
|
|
= DefinitionOperation OperationDefinition
|
|
|
|
| DefinitionFragment FragmentDefinition
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
-- ** Operations
|
|
|
|
|
|
|
|
-- | Operation definition.
|
|
|
|
data OperationDefinition
|
|
|
|
= SelectionSet SelectionSet
|
|
|
|
| OperationDefinition
|
|
|
|
OperationType
|
|
|
|
(Maybe Name)
|
|
|
|
[VariableDefinition]
|
|
|
|
[Directive]
|
|
|
|
SelectionSet
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
-- | 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.
|
2020-07-11 06:34:10 +02:00
|
|
|
data OperationType = Query | Mutation | Subscription deriving (Eq, Show)
|
2019-12-28 07:07:58 +01:00
|
|
|
|
|
|
|
-- ** Selection Sets
|
|
|
|
|
|
|
|
-- | "Top-level" selection, selection on an operation or fragment.
|
|
|
|
type SelectionSet = NonEmpty Selection
|
|
|
|
|
|
|
|
-- | Field selection.
|
|
|
|
type SelectionSetOpt = [Selection]
|
|
|
|
|
|
|
|
-- | Selection is a single entry in a selection set. It can be a single field,
|
|
|
|
-- fragment spread or inline fragment.
|
|
|
|
--
|
|
|
|
-- 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
|
|
|
|
-- }
|
|
|
|
-- }
|
|
|
|
-- @
|
|
|
|
--
|
|
|
|
-- 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
|
|
|
|
-- }
|
|
|
|
-- @
|
|
|
|
--
|
|
|
|
-- Inline fragments are similar but they don't have any name and the type
|
|
|
|
-- condition ("on UserType") is optional.
|
|
|
|
--
|
|
|
|
-- @
|
|
|
|
-- {
|
|
|
|
-- user {
|
|
|
|
-- ... on UserType {
|
|
|
|
-- id
|
|
|
|
-- name
|
|
|
|
-- }
|
|
|
|
-- }
|
|
|
|
-- @
|
|
|
|
data Selection
|
|
|
|
= Field (Maybe Alias) Name [Argument] [Directive] SelectionSetOpt
|
|
|
|
| FragmentSpread Name [Directive]
|
|
|
|
| InlineFragment (Maybe TypeCondition) [Directive] SelectionSet
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
-- ** Arguments
|
|
|
|
|
|
|
|
-- | Single argument.
|
|
|
|
--
|
|
|
|
-- @
|
|
|
|
-- {
|
|
|
|
-- user(id: 4) {
|
|
|
|
-- name
|
|
|
|
-- }
|
|
|
|
-- }
|
|
|
|
-- @
|
|
|
|
--
|
|
|
|
-- Here "id" is an argument for the field "user" and its value is 4.
|
|
|
|
data Argument = Argument Name Value deriving (Eq,Show)
|
|
|
|
|
|
|
|
-- ** Field Alias
|
|
|
|
|
|
|
|
-- | Alternative field name.
|
|
|
|
--
|
|
|
|
-- @
|
|
|
|
-- {
|
|
|
|
-- smallPic: profilePic(size: 64)
|
|
|
|
-- bigPic: profilePic(size: 1024)
|
|
|
|
-- }
|
|
|
|
-- @
|
|
|
|
--
|
|
|
|
-- Here "smallPic" and "bigPic" are aliases for the same field, "profilePic",
|
|
|
|
-- used to distinquish between profile pictures with different arguments
|
|
|
|
-- (sizes).
|
|
|
|
type Alias = Name
|
|
|
|
|
|
|
|
-- ** Fragments
|
|
|
|
|
|
|
|
-- | Fragment definition.
|
|
|
|
data FragmentDefinition
|
|
|
|
= FragmentDefinition Name TypeCondition [Directive] SelectionSet
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
-- | Type condition.
|
|
|
|
type TypeCondition = Name
|
|
|
|
|
|
|
|
-- ** Input Values
|
|
|
|
|
2020-05-22 10:11:48 +02:00
|
|
|
-- | Input value (literal or variable).
|
2019-12-28 07:07:58 +01:00
|
|
|
data Value
|
|
|
|
= Variable Name
|
|
|
|
| Int Int32
|
|
|
|
| Float Double
|
|
|
|
| String Text
|
|
|
|
| Boolean Bool
|
|
|
|
| Null
|
|
|
|
| Enum Name
|
|
|
|
| List [Value]
|
2020-05-22 10:11:48 +02:00
|
|
|
| Object [ObjectField Value]
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
-- | Constant input value.
|
|
|
|
data ConstValue
|
|
|
|
= ConstInt Int32
|
|
|
|
| ConstFloat Double
|
|
|
|
| ConstString Text
|
|
|
|
| ConstBoolean Bool
|
|
|
|
| ConstNull
|
|
|
|
| ConstEnum Name
|
|
|
|
| ConstList [ConstValue]
|
|
|
|
| ConstObject [ObjectField ConstValue]
|
2019-12-28 07:07:58 +01:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
-- | Key-value pair.
|
|
|
|
--
|
2020-05-22 10:11:48 +02:00
|
|
|
-- A list of 'ObjectField's represents a GraphQL object type.
|
|
|
|
data ObjectField a = ObjectField Name a
|
|
|
|
deriving (Eq, Show)
|
2019-12-28 07:07:58 +01:00
|
|
|
|
|
|
|
-- ** Variables
|
|
|
|
|
|
|
|
-- | Variable definition.
|
2020-05-22 10:11:48 +02:00
|
|
|
--
|
|
|
|
-- 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.
|
|
|
|
data VariableDefinition = VariableDefinition Name Type (Maybe ConstValue)
|
2019-12-28 07:07:58 +01:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
-- ** Type References
|
|
|
|
|
|
|
|
-- | Type representation.
|
|
|
|
data Type
|
|
|
|
= TypeNamed Name
|
|
|
|
| TypeList Type
|
|
|
|
| TypeNonNull NonNullType
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | Represents type names.
|
2019-12-28 07:07:58 +01:00
|
|
|
type NamedType = Name
|
|
|
|
|
|
|
|
-- | Helper type to represent Non-Null types and lists of such types.
|
|
|
|
data NonNullType
|
|
|
|
= NonNullTypeNamed Name
|
|
|
|
| NonNullTypeList Type
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
-- ** Directives
|
|
|
|
|
|
|
|
-- | Directive.
|
2020-02-14 06:20:05 +01:00
|
|
|
--
|
|
|
|
-- Directives begin with "@", can accept arguments, and can be applied to the
|
|
|
|
-- most GraphQL elements, providing additional information.
|
2019-12-28 07:07:58 +01:00
|
|
|
data Directive = Directive Name [Argument] deriving (Eq, Show)
|
|
|
|
|
2019-12-27 09:14:12 +01:00
|
|
|
-- * Type System
|
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | 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".
|
2019-12-26 13:00:47 +01:00
|
|
|
data TypeSystemDefinition
|
2020-01-25 16:37:17 +01:00
|
|
|
= SchemaDefinition [Directive] (NonEmpty OperationTypeDefinition)
|
2019-12-26 13:00:47 +01:00
|
|
|
| TypeDefinition TypeDefinition
|
2019-12-28 07:07:58 +01:00
|
|
|
| DirectiveDefinition
|
2020-01-15 20:20:50 +01:00
|
|
|
Description Name ArgumentsDefinition (NonEmpty DirectiveLocation)
|
2019-12-26 13:00:47 +01:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2019-12-27 09:14:12 +01:00
|
|
|
-- ** Type System Extensions
|
2019-12-26 13:00:47 +01:00
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | Extension for a type system definition. Only schema and type definitions
|
|
|
|
-- can be extended.
|
2019-12-26 13:00:47 +01:00
|
|
|
data TypeSystemExtension
|
|
|
|
= SchemaExtension SchemaExtension
|
|
|
|
| TypeExtension TypeExtension
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2019-12-27 09:14:12 +01:00
|
|
|
-- ** Schema
|
2019-12-26 13:00:47 +01:00
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | 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
|
|
|
|
-- }
|
|
|
|
-- @
|
2020-01-03 07:20:48 +01:00
|
|
|
data OperationTypeDefinition
|
|
|
|
= OperationTypeDefinition OperationType NamedType
|
2019-12-26 13:00:47 +01:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | Extension of the schema definition by further operations or directives.
|
2019-12-27 09:14:12 +01:00
|
|
|
data SchemaExtension
|
2020-01-25 16:37:17 +01:00
|
|
|
= SchemaOperationExtension [Directive] (NonEmpty OperationTypeDefinition)
|
2020-01-28 11:08:28 +01:00
|
|
|
| SchemaDirectivesExtension (NonEmpty Directive)
|
2019-12-26 13:00:47 +01:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2019-12-27 09:14:12 +01:00
|
|
|
-- ** Descriptions
|
2019-12-26 13:00:47 +01:00
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | 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
|
|
|
|
-- }
|
|
|
|
-- @
|
2019-12-27 09:14:12 +01:00
|
|
|
newtype Description = Description (Maybe Text)
|
2019-12-26 13:00:47 +01:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2019-12-27 09:14:12 +01:00
|
|
|
-- ** Types
|
2019-12-26 13:00:47 +01:00
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | Type definitions describe various user-defined types.
|
2019-12-26 13:00:47 +01:00
|
|
|
data TypeDefinition
|
|
|
|
= ScalarTypeDefinition Description Name [Directive]
|
2019-12-27 09:14:12 +01:00
|
|
|
| ObjectTypeDefinition
|
2020-01-07 13:56:58 +01:00
|
|
|
Description
|
|
|
|
Name
|
|
|
|
(ImplementsInterfaces [])
|
|
|
|
[Directive]
|
|
|
|
[FieldDefinition]
|
2019-12-26 13:00:47 +01:00
|
|
|
| InterfaceTypeDefinition Description Name [Directive] [FieldDefinition]
|
2020-01-07 13:56:58 +01:00
|
|
|
| UnionTypeDefinition Description Name [Directive] (UnionMemberTypes [])
|
2019-12-26 13:00:47 +01:00
|
|
|
| EnumTypeDefinition Description Name [Directive] [EnumValueDefinition]
|
2019-12-27 09:14:12 +01:00
|
|
|
| InputObjectTypeDefinition
|
2020-01-12 07:07:04 +01:00
|
|
|
Description Name [Directive] [InputValueDefinition]
|
2019-12-26 13:00:47 +01:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | Extensions for custom, already defined types.
|
2019-12-26 13:00:47 +01:00
|
|
|
data TypeExtension
|
|
|
|
= ScalarTypeExtension Name (NonEmpty Directive)
|
2019-12-27 09:14:12 +01:00
|
|
|
| ObjectTypeFieldsDefinitionExtension
|
2020-01-07 13:56:58 +01:00
|
|
|
Name (ImplementsInterfaces []) [Directive] (NonEmpty FieldDefinition)
|
2019-12-27 09:14:12 +01:00
|
|
|
| ObjectTypeDirectivesExtension
|
2020-01-07 13:56:58 +01:00
|
|
|
Name (ImplementsInterfaces []) (NonEmpty Directive)
|
|
|
|
| ObjectTypeImplementsInterfacesExtension
|
|
|
|
Name (ImplementsInterfaces NonEmpty)
|
2019-12-27 09:14:12 +01:00
|
|
|
| InterfaceTypeFieldsDefinitionExtension
|
|
|
|
Name [Directive] (NonEmpty FieldDefinition)
|
2019-12-26 13:00:47 +01:00
|
|
|
| InterfaceTypeDirectivesExtension Name (NonEmpty Directive)
|
2020-01-07 13:56:58 +01:00
|
|
|
| UnionTypeUnionMemberTypesExtension
|
|
|
|
Name [Directive] (UnionMemberTypes NonEmpty)
|
2020-01-26 11:55:15 +01:00
|
|
|
| UnionTypeDirectivesExtension Name (NonEmpty Directive)
|
2019-12-27 09:14:12 +01:00
|
|
|
| EnumTypeEnumValuesDefinitionExtension
|
|
|
|
Name [Directive] (NonEmpty EnumValueDefinition)
|
2019-12-26 13:00:47 +01:00
|
|
|
| EnumTypeDirectivesExtension Name (NonEmpty Directive)
|
2019-12-27 09:14:12 +01:00
|
|
|
| InputObjectTypeInputFieldsDefinitionExtension
|
2020-01-12 07:07:04 +01:00
|
|
|
Name [Directive] (NonEmpty InputValueDefinition)
|
2019-12-26 13:00:47 +01:00
|
|
|
| InputObjectTypeDirectivesExtension Name (NonEmpty Directive)
|
|
|
|
deriving (Eq, Show)
|
2019-12-27 09:14:12 +01:00
|
|
|
|
|
|
|
-- ** Objects
|
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | 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".
|
2020-01-07 13:56:58 +01:00
|
|
|
newtype ImplementsInterfaces t = ImplementsInterfaces (t NamedType)
|
2019-12-27 09:14:12 +01:00
|
|
|
|
2020-01-07 13:56:58 +01:00
|
|
|
instance Foldable t => Eq (ImplementsInterfaces t) where
|
|
|
|
(ImplementsInterfaces xs) == (ImplementsInterfaces ys)
|
|
|
|
= toList xs == toList ys
|
2020-01-05 07:42:04 +01:00
|
|
|
|
2020-01-07 13:56:58 +01:00
|
|
|
instance Foldable t => Show (ImplementsInterfaces t) where
|
|
|
|
show (ImplementsInterfaces interfaces) = Text.unpack
|
|
|
|
$ Text.append "implements"
|
|
|
|
$ Text.intercalate " & "
|
|
|
|
$ toList interfaces
|
2020-01-05 07:42:04 +01:00
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | 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.
|
2019-12-28 07:07:58 +01:00
|
|
|
data FieldDefinition
|
2020-01-05 07:42:04 +01:00
|
|
|
= FieldDefinition Description Name ArgumentsDefinition Type [Directive]
|
2019-12-27 09:14:12 +01:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | 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".
|
2019-12-27 09:14:12 +01:00
|
|
|
newtype ArgumentsDefinition = ArgumentsDefinition [InputValueDefinition]
|
|
|
|
deriving (Eq, Show)
|
|
|
|
|
2020-01-05 07:42:04 +01:00
|
|
|
instance Semigroup ArgumentsDefinition where
|
|
|
|
(ArgumentsDefinition xs) <> (ArgumentsDefinition ys) =
|
|
|
|
ArgumentsDefinition $ xs <> ys
|
|
|
|
|
|
|
|
instance Monoid ArgumentsDefinition where
|
|
|
|
mempty = ArgumentsDefinition []
|
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | 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".
|
2019-12-27 09:14:12 +01:00
|
|
|
data InputValueDefinition
|
2020-05-22 10:11:48 +02:00
|
|
|
= InputValueDefinition Description Name Type (Maybe ConstValue) [Directive]
|
2019-12-27 09:14:12 +01:00
|
|
|
deriving (Eq, Show)
|
|
|
|
|
|
|
|
-- ** Unions
|
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | List of types forming a union.
|
|
|
|
--
|
|
|
|
-- @
|
|
|
|
-- union SearchResult = Person | Photo
|
|
|
|
-- @
|
|
|
|
--
|
|
|
|
-- "Person" and "Photo" are member types of the union "SearchResult".
|
2020-01-07 13:56:58 +01:00
|
|
|
newtype UnionMemberTypes t = UnionMemberTypes (t NamedType)
|
2019-12-27 09:14:12 +01:00
|
|
|
|
2020-01-07 13:56:58 +01:00
|
|
|
instance Foldable t => Eq (UnionMemberTypes t) where
|
|
|
|
(UnionMemberTypes xs) == (UnionMemberTypes ys) = toList xs == toList ys
|
|
|
|
|
|
|
|
instance Foldable t => Show (UnionMemberTypes t) where
|
|
|
|
show (UnionMemberTypes memberTypes) = Text.unpack
|
|
|
|
$ Text.intercalate " | "
|
|
|
|
$ toList memberTypes
|
2019-12-27 09:14:12 +01:00
|
|
|
|
|
|
|
-- ** Enums
|
|
|
|
|
2020-02-14 06:20:05 +01:00
|
|
|
-- | 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".
|
2019-12-27 09:14:12 +01:00
|
|
|
data EnumValueDefinition = EnumValueDefinition Description Name [Directive]
|
|
|
|
deriving (Eq, Show)
|