Parse complete TypeSystemDefinition

This commit is contained in:
Eugen Wissner 2020-01-15 20:20:50 +01:00
parent d257d05d4e
commit ba710a3c96
6 changed files with 78 additions and 21 deletions

View File

@ -9,7 +9,7 @@ and this project adheres to
## [Unreleased] ## [Unreleased]
### Added ### Added
- AST for the GraphQL schema. - AST for the GraphQL schema.
- Parser for the SchemaDefinition and TypeDefinition. - Parser for the TypeSystemDefinition.
- `Trans.argument`. - `Trans.argument`.
### Changed ### Changed

View File

@ -248,7 +248,7 @@ data TypeSystemDefinition
= SchemaDefinition [Directive] OperationTypeDefinitions = SchemaDefinition [Directive] OperationTypeDefinitions
| TypeDefinition TypeDefinition | TypeDefinition TypeDefinition
| DirectiveDefinition | DirectiveDefinition
Description Name ArgumentsDefinition DirectiveLocation Description Name ArgumentsDefinition (NonEmpty DirectiveLocation)
deriving (Eq, Show) deriving (Eq, Show)
-- ** Type System Extensions -- ** Type System Extensions

View File

@ -51,6 +51,7 @@ import Text.Megaparsec ( Parsec
) )
import Text.Megaparsec.Char (char, digitChar, space1) import Text.Megaparsec.Char (char, digitChar, space1)
import qualified Text.Megaparsec.Char.Lexer as Lexer import qualified Text.Megaparsec.Char.Lexer as Lexer
import Data.Text (Text)
import qualified Data.Text as T import qualified Data.Text as T
import qualified Data.Text.Lazy as TL import qualified Data.Text.Lazy as TL
@ -87,8 +88,8 @@ dollar :: Parser T.Text
dollar = symbol "$" dollar = symbol "$"
-- | Parser for "@". -- | Parser for "@".
at :: Parser Char at :: Parser Text
at = char '@' at = symbol "@"
-- | Parser for "&". -- | Parser for "&".
amp :: Parser T.Text amp :: Parser T.Text

View File

@ -9,7 +9,14 @@ module Language.GraphQL.AST.Parser
import Control.Applicative (Alternative(..), optional) import Control.Applicative (Alternative(..), optional)
import Control.Applicative.Combinators (sepBy1) import Control.Applicative.Combinators (sepBy1)
import qualified Control.Applicative.Combinators.NonEmpty as NonEmpty import qualified Control.Applicative.Combinators.NonEmpty as NonEmpty
import Data.List.NonEmpty (NonEmpty)
import Data.Text (Text) import Data.Text (Text)
import qualified Language.GraphQL.AST.DirectiveLocation as Directive
import Language.GraphQL.AST.DirectiveLocation
( DirectiveLocation
, ExecutableDirectiveLocation
, TypeSystemDirectiveLocation
)
import Language.GraphQL.AST.Document import Language.GraphQL.AST.Document
import Language.GraphQL.AST.Lexer import Language.GraphQL.AST.Lexer
import Text.Megaparsec (lookAhead, option, try, (<?>)) import Text.Megaparsec (lookAhead, option, try, (<?>))
@ -33,8 +40,50 @@ executableDefinition = DefinitionOperation <$> operationDefinition
typeSystemDefinition :: Parser TypeSystemDefinition typeSystemDefinition :: Parser TypeSystemDefinition
typeSystemDefinition = schemaDefinition typeSystemDefinition = schemaDefinition
<|> TypeDefinition <$> typeDefinition <|> TypeDefinition <$> typeDefinition
<|> directiveDefinition
<?> "TypeSystemDefinition" <?> "TypeSystemDefinition"
directiveDefinition :: Parser TypeSystemDefinition
directiveDefinition = DirectiveDefinition
<$> description
<* symbol "directive"
<* at
<*> name
<*> argumentsDefinition
<* symbol "on"
<*> directiveLocations
directiveLocations :: Parser (NonEmpty DirectiveLocation)
directiveLocations = optional pipe
*> directiveLocation `NonEmpty.sepBy1` pipe
directiveLocation :: Parser DirectiveLocation
directiveLocation
= Directive.ExecutableDirectiveLocation <$> executableDirectiveLocation
<|> Directive.TypeSystemDirectiveLocation <$> typeSystemDirectiveLocation
executableDirectiveLocation :: Parser ExecutableDirectiveLocation
executableDirectiveLocation = Directive.Query <$ symbol "QUERY"
<|> Directive.Mutation <$ symbol "MUTATION"
<|> Directive.Subscription <$ symbol "SUBSCRIPTION"
<|> Directive.Field <$ symbol "FIELD"
<|> Directive.FragmentDefinition <$ "FRAGMENT_DEFINITION"
<|> Directive.FragmentSpread <$ "FRAGMENT_SPREAD"
<|> Directive.InlineFragment <$ "INLINE_FRAGMENT"
typeSystemDirectiveLocation :: Parser TypeSystemDirectiveLocation
typeSystemDirectiveLocation = Directive.Schema <$ symbol "SCHEMA"
<|> Directive.Scalar <$ symbol "SCALAR"
<|> Directive.Object <$ symbol "OBJECT"
<|> Directive.FieldDefinition <$ symbol "FIELD_DEFINITION"
<|> Directive.ArgumentDefinition <$ symbol "ARGUMENT_DEFINITION"
<|> Directive.Interface <$ symbol "INTERFACE"
<|> Directive.Union <$ symbol "UNION"
<|> Directive.Enum <$ symbol "ENUM"
<|> Directive.EnumValue <$ symbol "ENUM_VALUE"
<|> Directive.InputObject <$ symbol "INPUT_OBJECT"
<|> Directive.InputFieldDefinition <$ symbol "INPUT_FIELD_DEFINITION"
typeDefinition :: Parser TypeDefinition typeDefinition :: Parser TypeDefinition
typeDefinition = scalarTypeDefinition typeDefinition = scalarTypeDefinition
<|> objectTypeDefinition <|> objectTypeDefinition
@ -49,7 +98,7 @@ scalarTypeDefinition = ScalarTypeDefinition
<$> description <$> description
<* symbol "scalar" <* symbol "scalar"
<*> name <*> name
<*> opt directives <*> directives
<?> "ScalarTypeDefinition" <?> "ScalarTypeDefinition"
objectTypeDefinition :: Parser TypeDefinition objectTypeDefinition :: Parser TypeDefinition
@ -58,7 +107,7 @@ objectTypeDefinition = ObjectTypeDefinition
<* symbol "type" <* symbol "type"
<*> name <*> name
<*> option (ImplementsInterfaces []) (implementsInterfaces sepBy1) <*> option (ImplementsInterfaces []) (implementsInterfaces sepBy1)
<*> opt directives <*> directives
<*> braces (many fieldDefinition) <*> braces (many fieldDefinition)
<?> "ObjectTypeDefinition" <?> "ObjectTypeDefinition"
@ -72,7 +121,7 @@ unionTypeDefinition = UnionTypeDefinition
<$> description <$> description
<* symbol "union" <* symbol "union"
<*> name <*> name
<*> opt directives <*> directives
<*> option (UnionMemberTypes []) (unionMemberTypes sepBy1) <*> option (UnionMemberTypes []) (unionMemberTypes sepBy1)
<?> "UnionTypeDefinition" <?> "UnionTypeDefinition"
@ -91,7 +140,7 @@ interfaceTypeDefinition = InterfaceTypeDefinition
<$> description <$> description
<* symbol "interface" <* symbol "interface"
<*> name <*> name
<*> opt directives <*> directives
<*> braces (many fieldDefinition) <*> braces (many fieldDefinition)
<?> "InterfaceTypeDefinition" <?> "InterfaceTypeDefinition"
@ -100,28 +149,28 @@ enumTypeDefinition = EnumTypeDefinition
<$> description <$> description
<* symbol "enum" <* symbol "enum"
<*> name <*> name
<*> opt directives <*> directives
<*> opt enumValuesDefinition <*> enumValuesDefinition
<?> "EnumTypeDefinition" <?> "EnumTypeDefinition"
where where
enumValuesDefinition = braces (some enumValueDefinition) enumValuesDefinition = listOptIn braces enumValueDefinition
inputObjectTypeDefinition :: Parser TypeDefinition inputObjectTypeDefinition :: Parser TypeDefinition
inputObjectTypeDefinition = InputObjectTypeDefinition inputObjectTypeDefinition = InputObjectTypeDefinition
<$> description <$> description
<* symbol "input" <* symbol "input"
<*> name <*> name
<*> opt directives <*> directives
<*> opt inputFieldsDefinition <*> inputFieldsDefinition
<?> "InputObjectTypeDefinition" <?> "InputObjectTypeDefinition"
where where
inputFieldsDefinition = braces (some inputValueDefinition) inputFieldsDefinition = listOptIn braces inputValueDefinition
enumValueDefinition :: Parser EnumValueDefinition enumValueDefinition :: Parser EnumValueDefinition
enumValueDefinition = EnumValueDefinition enumValueDefinition = EnumValueDefinition
<$> description <$> description
<*> enumValue <*> enumValue
<*> opt directives <*> directives
<?> "EnumValueDefinition" <?> "EnumValueDefinition"
implementsInterfaces :: implementsInterfaces ::
@ -141,28 +190,28 @@ inputValueDefinition = InputValueDefinition
<* colon <* colon
<*> type' <*> type'
<*> defaultValue <*> defaultValue
<*> opt directives <*> directives
<?> "InputValueDefinition" <?> "InputValueDefinition"
argumentsDefinition :: Parser ArgumentsDefinition argumentsDefinition :: Parser ArgumentsDefinition
argumentsDefinition = ArgumentsDefinition argumentsDefinition = ArgumentsDefinition
<$> parens (many inputValueDefinition) <$> listOptIn parens inputValueDefinition
<?> "ArgumentsDefinition" <?> "ArgumentsDefinition"
fieldDefinition :: Parser FieldDefinition fieldDefinition :: Parser FieldDefinition
fieldDefinition = FieldDefinition fieldDefinition = FieldDefinition
<$> description <$> description
<*> name <*> name
<*> opt argumentsDefinition <*> argumentsDefinition
<* colon <* colon
<*> type' <*> type'
<*> opt directives <*> directives
<?> "FieldDefinition" <?> "FieldDefinition"
schemaDefinition :: Parser TypeSystemDefinition schemaDefinition :: Parser TypeSystemDefinition
schemaDefinition = SchemaDefinition schemaDefinition = SchemaDefinition
<$ symbol "schema" <$ symbol "schema"
<*> opt directives <*> directives
<*> operationTypeDefinitions <*> operationTypeDefinitions
<?> "SchemaDefinition" <?> "SchemaDefinition"
where where

View File

@ -77,7 +77,7 @@ spec = describe "Lexer" $ do
parse spread "" "..." `shouldParse` "..." parse spread "" "..." `shouldParse` "..."
parse colon "" ":" `shouldParse` ":" parse colon "" ":" `shouldParse` ":"
parse equals "" "=" `shouldParse` "=" parse equals "" "=" `shouldParse` "="
parse at "" "@" `shouldParse` '@' parse at "" "@" `shouldParse` "@"
runBetween brackets `shouldSucceedOn` "[]" runBetween brackets `shouldSucceedOn` "[]"
runBetween braces `shouldSucceedOn` "{}" runBetween braces `shouldSucceedOn` "{}"
parse pipe "" "|" `shouldParse` "|" parse pipe "" "|" `shouldParse` "|"

View File

@ -109,3 +109,10 @@ spec = describe "Parser" $ do
y: Float y: Float
} }
|] |]
it "parses minimal input enum definition with an optional pipe" $
parse document "" `shouldSucceedOn` [r|
directive @example on
| FIELD
| FRAGMENT_SPREAD
|]