2017-01-28 18:15:14 +01:00
|
|
|
{-# LANGUAGE LambdaCase #-}
|
2019-06-21 10:44:58 +02:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2019-09-25 05:35:36 +02:00
|
|
|
|
|
|
|
-- | @GraphQL@ document parser.
|
2019-11-03 10:42:10 +01:00
|
|
|
module Language.GraphQL.AST.Parser
|
2019-07-14 05:58:05 +02:00
|
|
|
( document
|
|
|
|
) where
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2019-12-25 06:45:29 +01:00
|
|
|
import Control.Applicative (Alternative(..), optional)
|
2020-01-12 07:19:28 +01:00
|
|
|
import qualified Control.Applicative.Combinators.NonEmpty as NonEmpty
|
2020-01-07 13:56:58 +01:00
|
|
|
import Control.Applicative.Combinators (sepBy, sepBy1)
|
|
|
|
import Data.Text (Text)
|
2020-01-03 07:20:48 +01:00
|
|
|
import Language.GraphQL.AST.Document
|
2019-11-03 10:42:10 +01:00
|
|
|
import Language.GraphQL.AST.Lexer
|
2019-12-25 06:45:29 +01:00
|
|
|
import Text.Megaparsec (lookAhead, option, try, (<?>))
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2019-08-26 10:14:46 +02:00
|
|
|
-- | Parser for the GraphQL documents.
|
2020-01-03 07:20:48 +01:00
|
|
|
document :: Parser Document
|
2019-12-25 06:45:29 +01:00
|
|
|
document = unicodeBOM
|
|
|
|
>> spaceConsumer
|
2020-01-03 07:20:48 +01:00
|
|
|
>> lexeme (NonEmpty.some definition)
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2020-01-03 07:20:48 +01:00
|
|
|
definition :: Parser Definition
|
|
|
|
definition = ExecutableDefinition <$> executableDefinition
|
|
|
|
<|> TypeSystemDefinition <$> typeSystemDefinition
|
|
|
|
<?> "Definition"
|
|
|
|
|
|
|
|
executableDefinition :: Parser ExecutableDefinition
|
|
|
|
executableDefinition = DefinitionOperation <$> operationDefinition
|
|
|
|
<|> DefinitionFragment <$> fragmentDefinition
|
|
|
|
<?> "ExecutableDefinition"
|
|
|
|
|
|
|
|
typeSystemDefinition :: Parser TypeSystemDefinition
|
|
|
|
typeSystemDefinition = schemaDefinition
|
2020-01-05 07:42:04 +01:00
|
|
|
<|> TypeDefinition <$> typeDefinition
|
|
|
|
<?> "TypeSystemDefinition"
|
|
|
|
|
|
|
|
typeDefinition :: Parser TypeDefinition
|
|
|
|
typeDefinition = scalarTypeDefinition
|
|
|
|
<|> objectTypeDefinition
|
2020-01-11 08:32:25 +01:00
|
|
|
<|> interfaceTypeDefinition
|
2020-01-07 13:56:58 +01:00
|
|
|
<|> unionTypeDefinition
|
2020-01-05 07:42:04 +01:00
|
|
|
<?> "TypeDefinition"
|
|
|
|
|
|
|
|
scalarTypeDefinition :: Parser TypeDefinition
|
|
|
|
scalarTypeDefinition = ScalarTypeDefinition
|
|
|
|
<$> description
|
|
|
|
<* symbol "scalar"
|
|
|
|
<*> name
|
|
|
|
<*> opt directives
|
|
|
|
<?> "ScalarTypeDefinition"
|
|
|
|
|
|
|
|
objectTypeDefinition :: Parser TypeDefinition
|
|
|
|
objectTypeDefinition = ObjectTypeDefinition
|
|
|
|
<$> description
|
|
|
|
<* symbol "type"
|
|
|
|
<*> name
|
2020-01-07 13:56:58 +01:00
|
|
|
<*> option (ImplementsInterfaces []) (implementsInterfaces sepBy1)
|
2020-01-05 07:42:04 +01:00
|
|
|
<*> opt directives
|
|
|
|
<*> braces (many fieldDefinition)
|
|
|
|
<?> "ObjectTypeDefinition"
|
|
|
|
|
|
|
|
description :: Parser Description
|
|
|
|
description = Description
|
|
|
|
<$> optional (string <|> blockString)
|
|
|
|
<?> "Description"
|
|
|
|
|
2020-01-07 13:56:58 +01:00
|
|
|
unionTypeDefinition :: Parser TypeDefinition
|
|
|
|
unionTypeDefinition = UnionTypeDefinition
|
|
|
|
<$> description
|
|
|
|
<* symbol "union"
|
|
|
|
<*> name
|
|
|
|
<*> opt directives
|
|
|
|
<*> option (UnionMemberTypes []) (unionMemberTypes sepBy1)
|
|
|
|
<?> "UnionTypeDefinition"
|
|
|
|
|
|
|
|
unionMemberTypes ::
|
|
|
|
Foldable t =>
|
|
|
|
(Parser Text -> Parser Text -> Parser (t NamedType)) ->
|
|
|
|
Parser (UnionMemberTypes t)
|
|
|
|
unionMemberTypes sepBy' = UnionMemberTypes
|
|
|
|
<$ equals
|
|
|
|
<* optional pipe
|
|
|
|
<*> name `sepBy'` pipe
|
|
|
|
<?> "UnionMemberTypes"
|
2020-01-05 07:42:04 +01:00
|
|
|
|
2020-01-11 08:32:25 +01:00
|
|
|
interfaceTypeDefinition :: Parser TypeDefinition
|
|
|
|
interfaceTypeDefinition = InterfaceTypeDefinition
|
|
|
|
<$> description
|
|
|
|
<* symbol "interface"
|
|
|
|
<*> name
|
|
|
|
<*> opt directives
|
|
|
|
<*> braces (many fieldDefinition)
|
|
|
|
<?> "InterfaceTypeDefinition"
|
|
|
|
|
2020-01-07 13:56:58 +01:00
|
|
|
implementsInterfaces ::
|
|
|
|
Foldable t =>
|
|
|
|
(Parser Text -> Parser Text -> Parser (t NamedType)) ->
|
|
|
|
Parser (ImplementsInterfaces t)
|
|
|
|
implementsInterfaces sepBy' = ImplementsInterfaces
|
2020-01-05 07:42:04 +01:00
|
|
|
<$ symbol "implements"
|
|
|
|
<* optional amp
|
2020-01-07 13:56:58 +01:00
|
|
|
<*> name `sepBy'` amp
|
2020-01-05 07:42:04 +01:00
|
|
|
<?> "ImplementsInterfaces"
|
|
|
|
|
|
|
|
inputValueDefinition :: Parser InputValueDefinition
|
|
|
|
inputValueDefinition = InputValueDefinition
|
|
|
|
<$> description
|
|
|
|
<*> name
|
|
|
|
<* colon
|
|
|
|
<*> type'
|
|
|
|
<*> defaultValue
|
|
|
|
<*> opt directives
|
|
|
|
<?> "InputValueDefinition"
|
|
|
|
|
|
|
|
argumentsDefinition :: Parser ArgumentsDefinition
|
|
|
|
argumentsDefinition = ArgumentsDefinition
|
|
|
|
<$> parens (many inputValueDefinition)
|
|
|
|
<?> "ArgumentsDefinition"
|
|
|
|
|
|
|
|
fieldDefinition :: Parser FieldDefinition
|
|
|
|
fieldDefinition = FieldDefinition
|
|
|
|
<$> description
|
|
|
|
<*> name
|
|
|
|
<*> opt argumentsDefinition
|
|
|
|
<* colon
|
|
|
|
<*> type'
|
|
|
|
<*> opt directives
|
|
|
|
<?> "FieldDefinition"
|
2020-01-03 07:20:48 +01:00
|
|
|
|
|
|
|
schemaDefinition :: Parser TypeSystemDefinition
|
|
|
|
schemaDefinition = SchemaDefinition
|
|
|
|
<$ symbol "schema"
|
|
|
|
<*> opt directives
|
|
|
|
<*> operationTypeDefinitions
|
|
|
|
<?> "SchemaDefinition"
|
|
|
|
|
|
|
|
operationTypeDefinitions :: Parser OperationTypeDefinitions
|
|
|
|
operationTypeDefinitions = braces $ manyNE operationTypeDefinition
|
|
|
|
|
|
|
|
operationTypeDefinition :: Parser OperationTypeDefinition
|
|
|
|
operationTypeDefinition = OperationTypeDefinition
|
|
|
|
<$> operationType <* colon
|
|
|
|
<*> name
|
|
|
|
<?> "OperationTypeDefinition"
|
2015-09-13 13:51:37 +02:00
|
|
|
|
|
|
|
operationDefinition :: Parser OperationDefinition
|
2019-12-28 07:07:58 +01:00
|
|
|
operationDefinition = SelectionSet <$> selectionSet
|
|
|
|
<|> operationDefinition'
|
|
|
|
<?> "operationDefinition error"
|
|
|
|
where
|
|
|
|
operationDefinition'
|
|
|
|
= OperationDefinition <$> operationType
|
|
|
|
<*> optional name
|
2020-01-13 08:11:22 +01:00
|
|
|
<*> variableDefinitions
|
|
|
|
<*> directives
|
2019-12-28 07:07:58 +01:00
|
|
|
<*> selectionSet
|
2015-09-13 17:44:31 +02:00
|
|
|
|
2017-01-28 18:15:14 +01:00
|
|
|
operationType :: Parser OperationType
|
2019-06-21 10:44:58 +02:00
|
|
|
operationType = Query <$ symbol "query"
|
|
|
|
<|> Mutation <$ symbol "mutation"
|
2020-01-03 07:20:48 +01:00
|
|
|
-- <?> Keep default error message
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2017-01-28 18:15:14 +01:00
|
|
|
-- * SelectionSet
|
2015-09-13 13:51:37 +02:00
|
|
|
|
|
|
|
selectionSet :: Parser SelectionSet
|
2020-01-12 07:19:28 +01:00
|
|
|
selectionSet = braces $ NonEmpty.some selection
|
2017-01-28 18:15:14 +01:00
|
|
|
|
|
|
|
selectionSetOpt :: Parser SelectionSetOpt
|
2020-01-13 08:11:22 +01:00
|
|
|
selectionSetOpt = listOptIn braces selection
|
2015-09-13 13:51:37 +02:00
|
|
|
|
|
|
|
selection :: Parser Selection
|
2019-12-25 06:45:29 +01:00
|
|
|
selection = field
|
|
|
|
<|> try fragmentSpread
|
|
|
|
<|> inlineFragment
|
|
|
|
<?> "selection error!"
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2017-01-28 18:15:14 +01:00
|
|
|
-- * Field
|
|
|
|
|
2019-12-25 06:45:29 +01:00
|
|
|
field :: Parser Selection
|
|
|
|
field = Field
|
|
|
|
<$> optional alias
|
|
|
|
<*> name
|
2020-01-13 08:11:22 +01:00
|
|
|
<*> arguments
|
|
|
|
<*> directives
|
|
|
|
<*> selectionSetOpt
|
2015-09-13 13:51:37 +02:00
|
|
|
|
|
|
|
alias :: Parser Alias
|
2019-06-21 10:44:58 +02:00
|
|
|
alias = try $ name <* colon
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2017-01-28 18:15:14 +01:00
|
|
|
-- * Arguments
|
|
|
|
|
2019-10-01 06:59:30 +02:00
|
|
|
arguments :: Parser [Argument]
|
2020-01-13 08:11:22 +01:00
|
|
|
arguments = listOptIn parens argument
|
2015-09-13 13:51:37 +02:00
|
|
|
|
|
|
|
argument :: Parser Argument
|
2019-06-21 10:44:58 +02:00
|
|
|
argument = Argument <$> name <* colon <*> value
|
2015-09-13 13:51:37 +02:00
|
|
|
|
|
|
|
-- * Fragments
|
|
|
|
|
2019-12-25 06:45:29 +01:00
|
|
|
fragmentSpread :: Parser Selection
|
|
|
|
fragmentSpread = FragmentSpread
|
|
|
|
<$ spread
|
|
|
|
<*> fragmentName
|
2020-01-13 08:11:22 +01:00
|
|
|
<*> directives
|
2019-12-25 06:45:29 +01:00
|
|
|
|
|
|
|
inlineFragment :: Parser Selection
|
|
|
|
inlineFragment = InlineFragment
|
|
|
|
<$ spread
|
|
|
|
<*> optional typeCondition
|
2020-01-13 08:11:22 +01:00
|
|
|
<*> directives
|
2019-12-25 06:45:29 +01:00
|
|
|
<*> selectionSet
|
2015-09-13 13:51:37 +02:00
|
|
|
|
|
|
|
fragmentDefinition :: Parser FragmentDefinition
|
2015-09-14 11:49:20 +02:00
|
|
|
fragmentDefinition = FragmentDefinition
|
2019-06-21 10:44:58 +02:00
|
|
|
<$ symbol "fragment"
|
2017-01-28 18:15:14 +01:00
|
|
|
<*> name
|
|
|
|
<*> typeCondition
|
2020-01-13 08:11:22 +01:00
|
|
|
<*> directives
|
2017-01-28 18:15:14 +01:00
|
|
|
<*> selectionSet
|
|
|
|
|
2019-08-29 07:40:50 +02:00
|
|
|
fragmentName :: Parser Name
|
2019-06-21 10:44:58 +02:00
|
|
|
fragmentName = but (symbol "on") *> name
|
2015-09-13 13:51:37 +02:00
|
|
|
|
|
|
|
typeCondition :: Parser TypeCondition
|
2019-06-21 10:44:58 +02:00
|
|
|
typeCondition = symbol "on" *> name
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2017-01-28 18:15:14 +01:00
|
|
|
-- * Input Values
|
2015-09-13 13:51:37 +02:00
|
|
|
|
|
|
|
value :: Parser Value
|
2019-11-03 10:42:10 +01:00
|
|
|
value = Variable <$> variable
|
|
|
|
<|> Float <$> try float
|
|
|
|
<|> Int <$> integer
|
|
|
|
<|> Boolean <$> booleanValue
|
|
|
|
<|> Null <$ symbol "null"
|
|
|
|
<|> String <$> blockString
|
|
|
|
<|> String <$> string
|
|
|
|
<|> Enum <$> try enumValue
|
|
|
|
<|> List <$> listValue
|
|
|
|
<|> Object <$> objectValue
|
2015-09-21 09:28:51 +02:00
|
|
|
<?> "value error!"
|
2017-01-28 18:15:14 +01:00
|
|
|
where
|
|
|
|
booleanValue :: Parser Bool
|
2019-06-21 10:44:58 +02:00
|
|
|
booleanValue = True <$ symbol "true"
|
|
|
|
<|> False <$ symbol "false"
|
2015-09-18 18:11:11 +02:00
|
|
|
|
2017-01-28 18:15:14 +01:00
|
|
|
enumValue :: Parser Name
|
2019-06-21 10:44:58 +02:00
|
|
|
enumValue = but (symbol "true") *> but (symbol "false") *> but (symbol "null") *> name
|
2015-09-18 18:11:11 +02:00
|
|
|
|
2017-01-28 18:15:14 +01:00
|
|
|
listValue :: Parser [Value]
|
2019-06-21 10:44:58 +02:00
|
|
|
listValue = brackets $ some value
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2017-01-28 18:15:14 +01:00
|
|
|
objectValue :: Parser [ObjectField]
|
2019-06-21 10:44:58 +02:00
|
|
|
objectValue = braces $ some objectField
|
2015-09-13 13:51:37 +02:00
|
|
|
|
|
|
|
objectField :: Parser ObjectField
|
2020-01-05 07:42:04 +01:00
|
|
|
objectField = ObjectField <$> name <* colon <*> value
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2017-01-28 18:15:14 +01:00
|
|
|
-- * Variables
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2019-10-01 06:59:30 +02:00
|
|
|
variableDefinitions :: Parser [VariableDefinition]
|
2020-01-13 08:11:22 +01:00
|
|
|
variableDefinitions = listOptIn parens variableDefinition
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2017-01-28 18:15:14 +01:00
|
|
|
variableDefinition :: Parser VariableDefinition
|
2020-01-13 08:11:22 +01:00
|
|
|
variableDefinition = VariableDefinition
|
|
|
|
<$> variable
|
|
|
|
<* colon
|
2020-01-05 07:42:04 +01:00
|
|
|
<*> type'
|
|
|
|
<*> defaultValue
|
|
|
|
<?> "VariableDefinition"
|
2020-01-13 08:11:22 +01:00
|
|
|
|
2019-07-18 05:10:02 +02:00
|
|
|
variable :: Parser Name
|
2019-06-21 10:44:58 +02:00
|
|
|
variable = dollar *> name
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2020-01-05 07:42:04 +01:00
|
|
|
defaultValue :: Parser (Maybe Value)
|
|
|
|
defaultValue = optional (equals *> value) <?> "DefaultValue"
|
2017-01-28 18:15:14 +01:00
|
|
|
|
|
|
|
-- * Input Types
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2020-01-05 07:42:04 +01:00
|
|
|
type' :: Parser Type
|
|
|
|
type' = try (TypeNonNull <$> nonNullType)
|
|
|
|
<|> TypeList <$> brackets type'
|
2019-11-22 08:00:50 +01:00
|
|
|
<|> TypeNamed <$> name
|
2020-01-05 07:42:04 +01:00
|
|
|
<?> "Type"
|
2015-09-13 13:51:37 +02:00
|
|
|
|
|
|
|
nonNullType :: Parser NonNullType
|
2019-06-21 10:44:58 +02:00
|
|
|
nonNullType = NonNullTypeNamed <$> name <* bang
|
2020-01-05 07:42:04 +01:00
|
|
|
<|> NonNullTypeList <$> brackets type' <* bang
|
2015-09-21 09:28:51 +02:00
|
|
|
<?> "nonNullType error!"
|
2015-09-13 13:51:37 +02:00
|
|
|
|
2017-01-28 18:15:14 +01:00
|
|
|
-- * Directives
|
|
|
|
|
2019-10-01 06:59:30 +02:00
|
|
|
directives :: Parser [Directive]
|
2020-01-13 08:11:22 +01:00
|
|
|
directives = many directive
|
2017-01-28 18:15:14 +01:00
|
|
|
|
|
|
|
directive :: Parser Directive
|
|
|
|
directive = Directive
|
2020-01-13 08:11:22 +01:00
|
|
|
<$ at
|
|
|
|
<*> name
|
|
|
|
<*> arguments
|
2017-01-28 18:15:14 +01:00
|
|
|
|
2015-09-13 13:51:37 +02:00
|
|
|
-- * Internal
|
|
|
|
|
2020-01-13 08:11:22 +01:00
|
|
|
listOptIn :: (Parser [a] -> Parser [a]) -> Parser a -> Parser [a]
|
|
|
|
listOptIn surround = option [] . surround . some
|
2017-01-28 18:15:14 +01:00
|
|
|
|
|
|
|
-- Hack to reverse parser success
|
|
|
|
but :: Parser a -> Parser ()
|
|
|
|
but pn = False <$ lookAhead pn <|> pure True >>= \case
|
2019-06-21 10:44:58 +02:00
|
|
|
False -> empty
|
|
|
|
True -> pure ()
|