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

189 lines
4.8 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
import Language.GraphQL.AST
2019-12-26 13:00:47 +01:00
import qualified Language.GraphQL.AST.Document as Document
import Language.GraphQL.AST.Lexer
import Text.Megaparsec (lookAhead, option, try, (<?>))
-- | Parser for the GraphQL documents.
2019-12-26 13:00:47 +01:00
document :: Parser Document.Document
document = unicodeBOM
>> spaceConsumer
>> lexeme (NonEmpty.some $ Document.ExecutableDefinition <$> definition)
definition :: Parser ExecutableDefinition
definition = DefinitionOperation <$> operationDefinition
<|> DefinitionFragment <$> fragmentDefinition
<?> "definition error!"
operationDefinition :: Parser OperationDefinition
2019-12-28 07:07:58 +01:00
operationDefinition = SelectionSet <$> selectionSet
<|> operationDefinition'
<?> "operationDefinition error"
where
operationDefinition'
= OperationDefinition <$> operationType
<*> optional name
<*> opt variableDefinitions
<*> opt directives
<*> selectionSet
operationType :: Parser OperationType
2019-06-21 10:44:58 +02:00
operationType = Query <$ symbol "query"
<|> Mutation <$ symbol "mutation"
<?> "operationType error"
-- * SelectionSet
selectionSet :: Parser SelectionSet
selectionSet = braces $ NonEmpty.some selection
selectionSetOpt :: Parser SelectionSetOpt
2019-06-21 10:44:58 +02:00
selectionSetOpt = braces $ some selection
selection :: Parser Selection
selection = field
<|> try fragmentSpread
<|> inlineFragment
<?> "selection error!"
-- * Field
field :: Parser Selection
field = Field
<$> optional alias
<*> name
<*> opt arguments
<*> opt directives
<*> opt selectionSetOpt
alias :: Parser Alias
2019-06-21 10:44:58 +02:00
alias = try $ name <* colon
-- * Arguments
arguments :: Parser [Argument]
2019-06-21 10:44:58 +02:00
arguments = parens $ some 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
<*> opt directives
inlineFragment :: Parser Selection
inlineFragment = InlineFragment
<$ spread
<*> optional typeCondition
<*> opt directives
<*> selectionSet
fragmentDefinition :: Parser FragmentDefinition
fragmentDefinition = FragmentDefinition
2019-06-21 10:44:58 +02:00
<$ symbol "fragment"
<*> name
<*> typeCondition
<*> opt 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
2019-06-21 10:44:58 +02:00
objectField = ObjectField <$> name <* symbol ":" <*> value
-- * Variables
variableDefinitions :: Parser [VariableDefinition]
2019-06-21 10:44:58 +02:00
variableDefinitions = parens $ some variableDefinition
variableDefinition :: Parser VariableDefinition
variableDefinition = VariableDefinition <$> variable
2019-06-21 10:44:58 +02:00
<* colon
<*> type_
<*> optional defaultValue
2019-07-18 05:10:02 +02:00
variable :: Parser Name
2019-06-21 10:44:58 +02:00
variable = dollar *> name
2019-07-18 05:10:02 +02:00
defaultValue :: Parser Value
2019-06-21 10:44:58 +02:00
defaultValue = equals *> value
-- * Input Types
type_ :: Parser Type
2019-11-22 08:00:50 +01:00
type_ = try (TypeNonNull <$> nonNullType)
<|> TypeList <$> brackets type_
<|> TypeNamed <$> name
<?> "type_ error!"
nonNullType :: Parser NonNullType
2019-06-21 10:44:58 +02:00
nonNullType = NonNullTypeNamed <$> name <* bang
<|> NonNullTypeList <$> brackets type_ <* bang
<?> "nonNullType error!"
-- * Directives
directives :: Parser [Directive]
2019-06-21 10:44:58 +02:00
directives = some directive
directive :: Parser Directive
directive = Directive
2019-06-21 10:44:58 +02:00
<$ at
<*> name
<*> opt arguments
-- * Internal
opt :: Monoid a => Parser a -> Parser a
opt = option mempty
-- 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 ()