Several improvements to the parser

- Add token combinator to simplify whitespace handling.
- Simplify whiteSpace parsers.
- Add `optempty` to handle pure mempty cases. `empty /= pure mempty`.
- Use `between` combinators for brackets, braces and parens.

This also includes small adjustments to the AST.
This commit is contained in:
Danny Navarro 2015-09-14 11:49:20 +02:00
parent b206079047
commit 62adfd89cd
2 changed files with 120 additions and 103 deletions

View File

@ -22,12 +22,12 @@ data OperationDefinition =
-- -- | Subscription Name [VariableDefinition] [Directive] SelectionSet -- -- | Subscription Name [VariableDefinition] [Directive] SelectionSet
deriving (Eq,Show) deriving (Eq,Show)
data VariableDefinition = VariableDefinition Variable Type DefaultValue data VariableDefinition = VariableDefinition Variable Type (Maybe DefaultValue)
deriving (Eq,Show) deriving (Eq,Show)
newtype Variable = Variable Name deriving (Eq,Show) newtype Variable = Variable Name deriving (Eq,Show)
newtype SelectionSet = SelectionSet [Selection] deriving (Eq,Show) type SelectionSet = [Selection]
data Selection = SelectionField Field data Selection = SelectionField Field
| SelectionFragmentSpread FragmentSpread | SelectionFragmentSpread FragmentSpread
@ -118,7 +118,7 @@ data FieldDefinition = FieldDefinition Name ArgumentsDefinition Type
type ArgumentsDefinition = [InputValueDefinition] type ArgumentsDefinition = [InputValueDefinition]
data InputValueDefinition = InputValueDefinition Name Type DefaultValue data InputValueDefinition = InputValueDefinition Name Type (Maybe DefaultValue)
deriving (Eq,Show) deriving (Eq,Show)
data InterfaceTypeDefinition = InterfaceTypeDefinition Name [FieldDefinition] data InterfaceTypeDefinition = InterfaceTypeDefinition Name [FieldDefinition]

View File

@ -2,9 +2,10 @@
module Data.GraphQL.Parser where module Data.GraphQL.Parser where
import Prelude hiding (takeWhile) import Prelude hiding (takeWhile)
import Control.Applicative (Alternative, (<|>), empty, many) import Control.Applicative (Alternative, (<|>), empty, many, optional)
import Data.Char import Data.Char
import Data.Text (Text)
import Data.Attoparsec.Text import Data.Attoparsec.Text
( Parser ( Parser
, (<?>) , (<?>)
@ -15,6 +16,7 @@ import Data.Attoparsec.Text
, isEndOfLine , isEndOfLine
, many1 , many1
, manyTill , manyTill
, option
, satisfy , satisfy
, sepBy , sepBy
, sepBy1 , sepBy1
@ -23,6 +25,7 @@ import Data.Attoparsec.Text
, skipWhile , skipWhile
, signed , signed
, space , space
, takeTill
, takeWhile , takeWhile
, takeWhile1 , takeWhile1
) )
@ -34,19 +37,18 @@ import Data.GraphQL.AST
-- XXX: Handle starting `_` and no number at the beginning: -- XXX: Handle starting `_` and no number at the beginning:
-- https://facebook.github.io/graphql/#sec-Names -- https://facebook.github.io/graphql/#sec-Names
name :: Parser Name name :: Parser Name
name = takeWhile1 isAlphaNum name = tok $ takeWhile1 isAlphaNum
-- * Document -- * Document
document :: Parser Document document :: Parser Document
document = s *> document = whiteSpace *>
(Document <$> many1_ definition (Document <$> many1 definition)
-- Try SelectionSet when no definition -- Try SelectionSet when no definition
<|> Document <$> pure <|> (Document . pure
<$> DefinitionOperation . DefinitionOperation
<$> Query mempty empty empty . Query mempty empty empty
<$> selectionSet) <$> selectionSet)
<* s
<?> "document error!" <?> "document error!"
definition :: Parser Definition definition :: Parser Definition
@ -61,30 +63,29 @@ operationDefinition =
<|> op Mutation "mutation" <|> op Mutation "mutation"
<?> "operationDefinition error!" <?> "operationDefinition error!"
where where
op f n = f <$ n <* s1 <*> name <* s1 op f n = f <$ tok n <*> tok name
<*> (variableDefinitions <* s <|> empty) <*> optempty variableDefinitions
<*> directives <* s <*> optempty directives
<*> selectionSet <*> selectionSet
variableDefinitions :: Parser [VariableDefinition] variableDefinitions :: Parser [VariableDefinition]
variableDefinitions = "(" *> s *> many1_ variableDefinition <* s <* ")" variableDefinitions = parens (many1 variableDefinition)
variableDefinition :: Parser VariableDefinition variableDefinition :: Parser VariableDefinition
variableDefinition = variableDefinition =
VariableDefinition <$> variable <* s <* ":" <* s VariableDefinition <$> variable
<*> type_ <* s <* tok ":"
<*> (defaultValue <|> empty) <*> type_
<*> optional defaultValue
defaultValue :: Parser DefaultValue defaultValue :: Parser DefaultValue
defaultValue = "=" *> s *> value defaultValue = tok "=" *> value
-- In defense of good taste, I'm taking liberty of not allowing space between
-- '$' and the 'name' even though that's not in the spec.
variable :: Parser Variable variable :: Parser Variable
variable = Variable <$ "$" <*> name variable = Variable <$ tok "$" <*> name
selectionSet :: Parser SelectionSet selectionSet :: Parser SelectionSet
selectionSet = "{" *> s *> (SelectionSet <$> many1_ selection) <* s <* "}" selectionSet = braces $ many1 selection
selection :: Parser Selection selection :: Parser Selection
selection = SelectionField <$> field selection = SelectionField <$> field
@ -94,44 +95,48 @@ selection = SelectionField <$> field
<?> "selection error!" <?> "selection error!"
field :: Parser Field field :: Parser Field
field = Field <$> (alias <* s1 <|> empty) field = Field <$> optempty alias
<*> name <* s <*> name
<*> (arguments <* s <|> empty) <*> optempty arguments
<*> directives <* s <*> optempty directives
<*> selectionSet <*> optempty selectionSet
<?> "field error!"
alias :: Parser Alias alias :: Parser Alias
alias = name <* s <* ":" alias = name <* tok ":"
arguments :: Parser [Argument] arguments :: Parser [Argument]
arguments = "(" *> s *> many1_ argument <* s <* ")" arguments = parens $ many1 argument
argument :: Parser Argument argument :: Parser Argument
argument = Argument <$> name <* s <* ":" <* s <*> value argument = Argument <$> name <* tok ":" <*> value
-- * Fragments -- * Fragments
fragmentSpread :: Parser FragmentSpread fragmentSpread :: Parser FragmentSpread
-- TODO: Make sure it fails when `... on`. -- TODO: Make sure it fails when `... on`.
-- See https://facebook.github.io/graphql/#FragmentSpread -- See https://facebook.github.io/graphql/#FragmentSpread
fragmentSpread = FragmentSpread <$ "..." <* s <*> name <* s1 <*> many_ directive fragmentSpread = FragmentSpread
<$ tok "..."
<*> name
<*> optempty directives
-- InlineFragment tried first in order to guard against 'on' keyword -- InlineFragment tried first in order to guard against 'on' keyword
inlineFragment :: Parser InlineFragment inlineFragment :: Parser InlineFragment
inlineFragment = InlineFragment <$ "..." <* s <* "on" <* s1 inlineFragment = InlineFragment
<*> typeCondition <* s <$ tok "..."
<*> directives <* s <* tok "on"
<*> selectionSet <*> typeCondition
<*> optempty directives
<*> selectionSet
fragmentDefinition :: Parser FragmentDefinition fragmentDefinition :: Parser FragmentDefinition
fragmentDefinition = fragmentDefinition = FragmentDefinition
FragmentDefinition <$ "fragment" <* s1 <$ tok "fragment"
<*> name <* s <*> name
<* "on" <* s1 <* tok "on"
<*> typeCondition <* s <*> typeCondition
<*> directives <* s <*> optempty directives
<*> selectionSet <*> selectionSet
typeCondition :: Parser TypeCondition typeCondition :: Parser TypeCondition
typeCondition = namedType typeCondition = namedType
@ -146,22 +151,22 @@ value = -- TODO: Handle arbitrary precision.
<|> ValueFloat <$> signed double <|> ValueFloat <$> signed double
<|> ValueBoolean <$> bool <|> ValueBoolean <$> bool
-- TODO: Handle escape characters, unicode, etc -- TODO: Handle escape characters, unicode, etc
<|> ValueString <$ "\"" <*> takeWhile isAlphaNum <* "\"" <|> ValueString <$ "\"" <*> takeWhile isAlphaNum <* "\""
-- `true` and `false` have been tried before -- `true` and `false` have been tried before
<|> ValueEnum <$> name <|> ValueEnum <$> name
<|> ValueList <$> listValue <|> ValueList <$> listValue
<|> ValueObject <$> objectValue <|> ValueObject <$> objectValue
-- Notice it can be empty -- Notice it can be empty
listValue :: Parser ListValue listValue :: Parser ListValue
listValue = ListValue <$ "[" <* s <*> many_ value <* s <* "]" listValue = ListValue <$> brackets (many value)
-- Notice it can be empty -- Notice it can be empty
objectValue :: Parser ObjectValue objectValue :: Parser ObjectValue
objectValue = ObjectValue <$ "{" <* s <*> many_ objectField <* s <* "}" objectValue = ObjectValue <$> braces (many objectField)
objectField :: Parser ObjectField objectField :: Parser ObjectField
objectField = ObjectField <$> name <* s <* ":" <* s <*> value objectField = ObjectField <$> name <* tok ":" <*> value
bool :: Parser Bool bool :: Parser Bool
bool = True <$ "true" bool = True <$ "true"
@ -170,10 +175,13 @@ bool = True <$ "true"
-- * Directives -- * Directives
directives :: Parser [Directive] directives :: Parser [Directive]
directives = many_ directive directives = many1 directive
directive :: Parser Directive directive :: Parser Directive
directive = Directive <$ "@" <*> name <* s <*> arguments directive = Directive
<$ tok "@"
<*> name
<*> optempty arguments
-- * Type Reference -- * Type Reference
@ -186,16 +194,14 @@ namedType :: Parser NamedType
namedType = NamedType <$> name namedType = NamedType <$> name
listType :: Parser ListType listType :: Parser ListType
listType = ListType <$ "[" <* s <*> type_ <* s <* "]" listType = ListType <$> brackets type_
nonNullType :: Parser NonNullType nonNullType :: Parser NonNullType
nonNullType = NonNullTypeNamed <$> namedType <* s <* "!" nonNullType = NonNullTypeNamed <$> namedType <* tok "!"
<|> NonNullTypeList <$> listType <* s <* "!" <|> NonNullTypeList <$> listType <* tok "!"
-- * Type Definition -- * Type Definition
-- TODO: what is Const Variable?
-- https://facebook.github.io/graphql/#Value
typeDefinition :: Parser TypeDefinition typeDefinition :: Parser TypeDefinition
typeDefinition = typeDefinition =
TypeDefinitionObject <$> objectTypeDefinition TypeDefinitionObject <$> objectTypeDefinition
@ -209,102 +215,113 @@ typeDefinition =
objectTypeDefinition :: Parser ObjectTypeDefinition objectTypeDefinition :: Parser ObjectTypeDefinition
objectTypeDefinition = ObjectTypeDefinition objectTypeDefinition = ObjectTypeDefinition
<$ "type" <* s1 <$ tok "type"
<*> name <* s1 <*> name
<*> (interfaces <* s <|> empty) <*> optempty interfaces
<*> fieldDefinitions <*> fieldDefinitions
<?> "objectTypeDefinition error!" <?> "objectTypeDefinition error!"
interfaces :: Parser Interfaces interfaces :: Parser Interfaces
interfaces = "implements" *> s1 *> many1_ namedType interfaces = tok "implements" *> many1 namedType
fieldDefinitions :: Parser [FieldDefinition] fieldDefinitions :: Parser [FieldDefinition]
fieldDefinitions = "{" *> s *> many1_ fieldDefinition <* s <* "}" fieldDefinitions = braces $ many1 fieldDefinition
fieldDefinition :: Parser FieldDefinition fieldDefinition :: Parser FieldDefinition
fieldDefinition = FieldDefinition fieldDefinition = FieldDefinition
<$> name <* s <$> name
<*> (argumentsDefinition <* s <|> empty) <*> optempty argumentsDefinition
<* ":" <* s <* tok ":"
<*> type_ <*> type_
argumentsDefinition :: Parser ArgumentsDefinition argumentsDefinition :: Parser ArgumentsDefinition
argumentsDefinition = inputValueDefinitions argumentsDefinition = inputValueDefinitions
inputValueDefinitions :: Parser [InputValueDefinition] inputValueDefinitions :: Parser [InputValueDefinition]
inputValueDefinitions = "(" *> s *> many1_ inputValueDefinition <* s <* ")" inputValueDefinitions = parens $ many1 inputValueDefinition
inputValueDefinition :: Parser InputValueDefinition inputValueDefinition :: Parser InputValueDefinition
inputValueDefinition = InputValueDefinition inputValueDefinition = InputValueDefinition
<$> name <* s <$> name
<* ":" <* s <* tok ":"
<*> type_ <* s <*> type_
<*> (value <|> empty) <*> optional defaultValue
interfaceTypeDefinition :: Parser InterfaceTypeDefinition interfaceTypeDefinition :: Parser InterfaceTypeDefinition
interfaceTypeDefinition = InterfaceTypeDefinition interfaceTypeDefinition = InterfaceTypeDefinition
<$ "interface" <* s1 <$ tok "interface"
<*> name <* s <*> name
<*> fieldDefinitions <*> fieldDefinitions
unionTypeDefinition :: Parser UnionTypeDefinition unionTypeDefinition :: Parser UnionTypeDefinition
unionTypeDefinition = UnionTypeDefinition unionTypeDefinition = UnionTypeDefinition
<$ "union" <* s1 <$ tok "union"
<*> name <* s <*> name
<* "=" <* s <* tok "="
<*> unionMembers <*> unionMembers
where
-- This should take care of standalone `NamedType` unionMembers :: Parser [NamedType]
unionMembers = namedType `sepBy1` (s *> "|" <* s) unionMembers = namedType `sepBy1` tok "|"
scalarTypeDefinition :: Parser ScalarTypeDefinition scalarTypeDefinition :: Parser ScalarTypeDefinition
scalarTypeDefinition = ScalarTypeDefinition <$ "scalar" <* s1 <*> name scalarTypeDefinition = ScalarTypeDefinition
<$ tok "scalar"
<*> name
enumTypeDefinition :: Parser EnumTypeDefinition enumTypeDefinition :: Parser EnumTypeDefinition
enumTypeDefinition = EnumTypeDefinition enumTypeDefinition = EnumTypeDefinition
<$ "enum" <* s1 <$ tok "enum"
<*> name <* s <*> name
<*> enumValueDefinitions <*> enumValueDefinitions
enumValueDefinitions :: Parser [EnumValueDefinition] enumValueDefinitions :: Parser [EnumValueDefinition]
enumValueDefinitions = "{" *> s *> many1_ enumValueDefinition <* s <* "}" enumValueDefinitions = braces $ many1 enumValueDefinition
enumValueDefinition :: Parser EnumValueDefinition enumValueDefinition :: Parser EnumValueDefinition
enumValueDefinition = EnumValueDefinition <$> name enumValueDefinition = EnumValueDefinition <$> name
inputObjectTypeDefinition :: Parser InputObjectTypeDefinition inputObjectTypeDefinition :: Parser InputObjectTypeDefinition
inputObjectTypeDefinition = InputObjectTypeDefinition inputObjectTypeDefinition = InputObjectTypeDefinition
<$ "input" <* s1 <$ tok "input"
<*> name <* s <*> name
<*> inputValueDefinitions <*> inputValueDefinitions
typeExtensionDefinition :: Parser TypeExtensionDefinition typeExtensionDefinition :: Parser TypeExtensionDefinition
typeExtensionDefinition = TypeExtensionDefinition typeExtensionDefinition = TypeExtensionDefinition
<$ "extend" <* s1 <$ tok "extend"
<*> objectTypeDefinition <*> objectTypeDefinition
-- * Internal -- * Internal
many_ :: Parser a -> Parser [a] tok :: Parser a -> Parser a
many_ = flip sepBy space' tok p = p <* whiteSpace
many1_ :: Parser a -> Parser [a] parens :: Parser a -> Parser a
many1_ = flip sepBy1 space' parens = between "(" ")"
space' :: Parser Char braces :: Parser a -> Parser a
space' = satisfy isSpace' braces = between "{" "}"
s :: Parser () brackets :: Parser a -> Parser a
s = comments <|> skipWhile isSpace' brackets = between "[" "]"
s1 :: Parser () between :: Parser Text -> Parser Text -> Parser a -> Parser a
s1 = comments <|> space' *> s between open close p = tok open *> p <* tok close
isSpace' :: Char -> Bool -- `empty` /= `pure mempty` for `Parser`.
isSpace' c = isSpace c || ',' == c || isEndOfLine c optempty :: Monoid a => Parser a -> Parser a
optempty = option mempty
-- ** WhiteSpace
--
whiteSpace :: Parser ()
whiteSpace = comments
<|> skipWhile (\c -> isSpace c
|| ',' == c
|| isEndOfLine c)
comments :: Parser () comments :: Parser ()
comments = skipMany comment comments = skipMany comment
comment :: Parser () comment :: Parser Text
comment = () <$ "#" <* manyTill anyChar endOfLine comment = "#" *> takeTill isEndOfLine