Parse enum and input object type definitions
This commit is contained in:
		| @@ -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 | - Parser for the SchemaDefinition and TypeDefinition. | ||||||
| - `Trans.argument`. | - `Trans.argument`. | ||||||
|  |  | ||||||
| ### Changed | ### Changed | ||||||
|   | |||||||
| @@ -12,6 +12,7 @@ module Language.GraphQL.AST.Document | |||||||
|     , Description(..) |     , Description(..) | ||||||
|     , Directive(..) |     , Directive(..) | ||||||
|     , Document |     , Document | ||||||
|  |     , EnumValueDefinition(..) | ||||||
|     , ExecutableDefinition(..) |     , ExecutableDefinition(..) | ||||||
|     , FieldDefinition(..) |     , FieldDefinition(..) | ||||||
|     , FragmentDefinition(..) |     , FragmentDefinition(..) | ||||||
| @@ -289,7 +290,7 @@ data TypeDefinition | |||||||
|     | UnionTypeDefinition Description Name [Directive] (UnionMemberTypes []) |     | UnionTypeDefinition Description Name [Directive] (UnionMemberTypes []) | ||||||
|     | EnumTypeDefinition Description Name [Directive] [EnumValueDefinition] |     | EnumTypeDefinition Description Name [Directive] [EnumValueDefinition] | ||||||
|     | InputObjectTypeDefinition |     | InputObjectTypeDefinition | ||||||
|         Description Name [Directive] InputFieldsDefinitionOpt |         Description Name [Directive] [InputValueDefinition] | ||||||
|     deriving (Eq, Show) |     deriving (Eq, Show) | ||||||
|  |  | ||||||
| data TypeExtension | data TypeExtension | ||||||
| @@ -310,7 +311,7 @@ data TypeExtension | |||||||
|         Name [Directive] (NonEmpty EnumValueDefinition) |         Name [Directive] (NonEmpty EnumValueDefinition) | ||||||
|     | EnumTypeDirectivesExtension Name (NonEmpty Directive) |     | EnumTypeDirectivesExtension Name (NonEmpty Directive) | ||||||
|     | InputObjectTypeInputFieldsDefinitionExtension |     | InputObjectTypeInputFieldsDefinitionExtension | ||||||
|         Name [Directive] InputFieldsDefinition |         Name [Directive] (NonEmpty InputValueDefinition) | ||||||
|     | InputObjectTypeDirectivesExtension Name (NonEmpty Directive) |     | InputObjectTypeDirectivesExtension Name (NonEmpty Directive) | ||||||
|     deriving (Eq, Show) |     deriving (Eq, Show) | ||||||
|  |  | ||||||
| @@ -362,13 +363,3 @@ instance Foldable t => Show (UnionMemberTypes t) where | |||||||
|  |  | ||||||
| data EnumValueDefinition = EnumValueDefinition Description Name [Directive] | data EnumValueDefinition = EnumValueDefinition Description Name [Directive] | ||||||
|     deriving (Eq, Show) |     deriving (Eq, Show) | ||||||
|  |  | ||||||
| -- ** Input Objects |  | ||||||
|  |  | ||||||
| newtype InputFieldsDefinition |  | ||||||
|     = InputFieldsDefinition (NonEmpty InputValueDefinition) |  | ||||||
|     deriving (Eq, Show) |  | ||||||
|  |  | ||||||
| newtype InputFieldsDefinitionOpt |  | ||||||
|     = InputFieldsDefinitionOpt [InputValueDefinition] |  | ||||||
|     deriving (Eq, Show) |  | ||||||
|   | |||||||
| @@ -7,8 +7,8 @@ module Language.GraphQL.AST.Parser | |||||||
|     ) where |     ) where | ||||||
|  |  | ||||||
| import Control.Applicative (Alternative(..), optional) | import Control.Applicative (Alternative(..), optional) | ||||||
|  | import Control.Applicative.Combinators (sepBy1) | ||||||
| import qualified Control.Applicative.Combinators.NonEmpty as NonEmpty | import qualified Control.Applicative.Combinators.NonEmpty as NonEmpty | ||||||
| import Control.Applicative.Combinators (sepBy, sepBy1) |  | ||||||
| import Data.Text (Text) | import Data.Text (Text) | ||||||
| import Language.GraphQL.AST.Document | import Language.GraphQL.AST.Document | ||||||
| import Language.GraphQL.AST.Lexer | import Language.GraphQL.AST.Lexer | ||||||
| @@ -40,6 +40,8 @@ typeDefinition = scalarTypeDefinition | |||||||
|     <|> objectTypeDefinition |     <|> objectTypeDefinition | ||||||
|     <|> interfaceTypeDefinition |     <|> interfaceTypeDefinition | ||||||
|     <|> unionTypeDefinition |     <|> unionTypeDefinition | ||||||
|  |     <|> enumTypeDefinition | ||||||
|  |     <|> inputObjectTypeDefinition | ||||||
|     <?> "TypeDefinition" |     <?> "TypeDefinition" | ||||||
|  |  | ||||||
| scalarTypeDefinition :: Parser TypeDefinition | scalarTypeDefinition :: Parser TypeDefinition | ||||||
| @@ -93,6 +95,35 @@ interfaceTypeDefinition = InterfaceTypeDefinition | |||||||
|     <*> braces (many fieldDefinition) |     <*> braces (many fieldDefinition) | ||||||
|     <?> "InterfaceTypeDefinition" |     <?> "InterfaceTypeDefinition" | ||||||
|  |  | ||||||
|  | enumTypeDefinition :: Parser TypeDefinition | ||||||
|  | enumTypeDefinition = EnumTypeDefinition | ||||||
|  |     <$> description | ||||||
|  |     <* symbol "enum" | ||||||
|  |     <*> name | ||||||
|  |     <*> opt directives | ||||||
|  |     <*> opt enumValuesDefinition | ||||||
|  |     <?> "EnumTypeDefinition" | ||||||
|  |   where | ||||||
|  |     enumValuesDefinition = braces (some enumValueDefinition) | ||||||
|  |  | ||||||
|  | inputObjectTypeDefinition :: Parser TypeDefinition | ||||||
|  | inputObjectTypeDefinition = InputObjectTypeDefinition | ||||||
|  |     <$> description | ||||||
|  |     <* symbol "input" | ||||||
|  |     <*> name | ||||||
|  |     <*> opt directives | ||||||
|  |     <*> opt inputFieldsDefinition | ||||||
|  |     <?> "InputObjectTypeDefinition" | ||||||
|  |   where | ||||||
|  |     inputFieldsDefinition = braces (some inputValueDefinition) | ||||||
|  |  | ||||||
|  | enumValueDefinition :: Parser EnumValueDefinition | ||||||
|  | enumValueDefinition = EnumValueDefinition | ||||||
|  |     <$> description | ||||||
|  |     <*> enumValue | ||||||
|  |     <*> opt directives | ||||||
|  |     <?> "EnumValueDefinition" | ||||||
|  |  | ||||||
| implementsInterfaces :: | implementsInterfaces :: | ||||||
|     Foldable t => |     Foldable t => | ||||||
|     (Parser Text -> Parser Text -> Parser (t NamedType)) -> |     (Parser Text -> Parser Text -> Parser (t NamedType)) -> | ||||||
| @@ -134,9 +165,8 @@ schemaDefinition = SchemaDefinition | |||||||
|     <*> opt directives |     <*> opt directives | ||||||
|     <*> operationTypeDefinitions |     <*> operationTypeDefinitions | ||||||
|     <?> "SchemaDefinition" |     <?> "SchemaDefinition" | ||||||
|  |   where | ||||||
| operationTypeDefinitions :: Parser OperationTypeDefinitions |     operationTypeDefinitions  = braces $ NonEmpty.some operationTypeDefinition | ||||||
| operationTypeDefinitions  = braces $ manyNE operationTypeDefinition |  | ||||||
|  |  | ||||||
| operationTypeDefinition :: Parser OperationTypeDefinition | operationTypeDefinition :: Parser OperationTypeDefinition | ||||||
| operationTypeDefinition = OperationTypeDefinition | operationTypeDefinition = OperationTypeDefinition | ||||||
| @@ -244,15 +274,15 @@ value = Variable <$> variable | |||||||
|     booleanValue = True  <$ symbol "true" |     booleanValue = True  <$ symbol "true" | ||||||
|                <|> False <$ symbol "false" |                <|> False <$ symbol "false" | ||||||
|  |  | ||||||
|     enumValue :: Parser Name |  | ||||||
|     enumValue = but (symbol "true") *> but (symbol "false") *> but (symbol "null") *> name |  | ||||||
|  |  | ||||||
|     listValue :: Parser [Value] |     listValue :: Parser [Value] | ||||||
|     listValue = brackets $ some value |     listValue = brackets $ some value | ||||||
|  |  | ||||||
|     objectValue :: Parser [ObjectField] |     objectValue :: Parser [ObjectField] | ||||||
|     objectValue = braces $ some objectField |     objectValue = braces $ some objectField | ||||||
|  |  | ||||||
|  | enumValue :: Parser Name | ||||||
|  | enumValue = but (symbol "true") *> but (symbol "false") *> but (symbol "null") *> name | ||||||
|  |  | ||||||
| objectField :: Parser ObjectField | objectField :: Parser ObjectField | ||||||
| objectField = ObjectField <$> name <* colon <*> value | objectField = ObjectField <$> name <* colon <*> value | ||||||
|  |  | ||||||
|   | |||||||
| @@ -81,3 +81,31 @@ spec = describe "Parser" $ do | |||||||
|               name: String |               name: String | ||||||
|             } |             } | ||||||
|         |] |         |] | ||||||
|  |  | ||||||
|  |     it "parses minimal enum type definition" $ | ||||||
|  |         parse document "" `shouldSucceedOn` [r| | ||||||
|  |             enum Direction { | ||||||
|  |               NORTH | ||||||
|  |               EAST | ||||||
|  |               SOUTH | ||||||
|  |               WEST | ||||||
|  |             } | ||||||
|  |         |] | ||||||
|  |  | ||||||
|  |     it "parses minimal enum type definition" $ | ||||||
|  |         parse document "" `shouldSucceedOn` [r| | ||||||
|  |             enum Direction { | ||||||
|  |               NORTH | ||||||
|  |               EAST | ||||||
|  |               SOUTH | ||||||
|  |               WEST | ||||||
|  |             } | ||||||
|  |         |] | ||||||
|  |  | ||||||
|  |     it "parses minimal input object type definition" $ | ||||||
|  |         parse document "" `shouldSucceedOn` [r| | ||||||
|  |             input Point2D { | ||||||
|  |               x: Float | ||||||
|  |               y: Float | ||||||
|  |             } | ||||||
|  |         |] | ||||||
|   | |||||||
		Reference in New Issue
	
	Block a user