graphql/src/Language/GraphQL/AST/Parser.hs

312 lines
8.0 KiB
Haskell
Raw Normal View History

{-# LANGUAGE LambdaCase #-}
2019-06-21 10:44:58 +02:00
{-# LANGUAGE OverloadedStrings #-}
-- | @GraphQL@ document parser.
module Language.GraphQL.AST.Parser
2019-07-14 05:58:05 +02:00
( document
) where
import Control.Applicative (Alternative(..), optional)
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
import Language.GraphQL.AST.Lexer
import Text.Megaparsec (lookAhead, option, try, (<?>))
-- | Parser for the GraphQL documents.
2020-01-03 07:20:48 +01:00
document :: Parser Document
document = unicodeBOM
>> spaceConsumer
2020-01-03 07:20:48 +01:00
>> lexeme (NonEmpty.some definition)
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"
operationDefinition :: Parser OperationDefinition
2019-12-28 07:07:58 +01:00
operationDefinition = SelectionSet <$> selectionSet
<|> operationDefinition'
<?> "operationDefinition error"
where
operationDefinition'
= OperationDefinition <$> operationType
<*> optional name
<*> variableDefinitions
<*> directives
2019-12-28 07:07:58 +01:00
<*> selectionSet
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
-- * SelectionSet
selectionSet :: Parser SelectionSet
selectionSet = braces $ NonEmpty.some selection
selectionSetOpt :: Parser SelectionSetOpt
selectionSetOpt = listOptIn braces selection
selection :: Parser Selection
selection = field
<|> try fragmentSpread
<|> inlineFragment
<?> "selection error!"
-- * Field
field :: Parser Selection
field = Field
<$> optional alias
<*> name
<*> arguments
<*> directives
<*> selectionSetOpt
alias :: Parser Alias
2019-06-21 10:44:58 +02:00
alias = try $ name <* colon
-- * Arguments
arguments :: Parser [Argument]
arguments = listOptIn parens argument
argument :: Parser Argument
2019-06-21 10:44:58 +02:00
argument = Argument <$> name <* colon <*> value
-- * Fragments
fragmentSpread :: Parser Selection
fragmentSpread = FragmentSpread
<$ spread
<*> fragmentName
<*> directives
inlineFragment :: Parser Selection
inlineFragment = InlineFragment
<$ spread
<*> optional typeCondition
<*> directives
<*> selectionSet
fragmentDefinition :: Parser FragmentDefinition
fragmentDefinition = FragmentDefinition
2019-06-21 10:44:58 +02:00
<$ symbol "fragment"
<*> name
<*> typeCondition
<*> directives
<*> selectionSet
fragmentName :: Parser Name
2019-06-21 10:44:58 +02:00
fragmentName = but (symbol "on") *> name
typeCondition :: Parser TypeCondition
2019-06-21 10:44:58 +02:00
typeCondition = symbol "on" *> name
-- * Input Values
value :: Parser Value
value = Variable <$> variable
<|> Float <$> try float
<|> Int <$> integer
<|> Boolean <$> booleanValue
<|> Null <$ symbol "null"
<|> String <$> blockString
<|> String <$> string
<|> Enum <$> try enumValue
<|> List <$> listValue
<|> Object <$> objectValue
<?> "value error!"
where
booleanValue :: Parser Bool
2019-06-21 10:44:58 +02:00
booleanValue = True <$ symbol "true"
<|> False <$ symbol "false"
enumValue :: Parser Name
2019-06-21 10:44:58 +02:00
enumValue = but (symbol "true") *> but (symbol "false") *> but (symbol "null") *> name
listValue :: Parser [Value]
2019-06-21 10:44:58 +02:00
listValue = brackets $ some value
objectValue :: Parser [ObjectField]
2019-06-21 10:44:58 +02:00
objectValue = braces $ some objectField
objectField :: Parser ObjectField
2020-01-05 07:42:04 +01:00
objectField = ObjectField <$> name <* colon <*> value
-- * Variables
variableDefinitions :: Parser [VariableDefinition]
variableDefinitions = listOptIn parens variableDefinition
variableDefinition :: Parser VariableDefinition
variableDefinition = VariableDefinition
<$> variable
<* colon
2020-01-05 07:42:04 +01:00
<*> type'
<*> defaultValue
<?> "VariableDefinition"
2019-07-18 05:10:02 +02:00
variable :: Parser Name
2019-06-21 10:44:58 +02:00
variable = dollar *> name
2020-01-05 07:42:04 +01:00
defaultValue :: Parser (Maybe Value)
defaultValue = optional (equals *> value) <?> "DefaultValue"
-- * Input Types
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"
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
<?> "nonNullType error!"
-- * Directives
directives :: Parser [Directive]
directives = many directive
directive :: Parser Directive
directive = Directive
<$ at
<*> name
<*> arguments
-- * Internal
listOptIn :: (Parser [a] -> Parser [a]) -> Parser a -> Parser [a]
listOptIn surround = option [] . surround . some
-- 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 ()