forked from OSS/graphql
		
	Draft the Validation API
This commit is contained in:
		| @@ -69,9 +69,9 @@ type Document = NonEmpty Definition | ||||
|  | ||||
| -- | All kinds of definitions that can occur in a GraphQL document. | ||||
| data Definition | ||||
|     = ExecutableDefinition ExecutableDefinition | ||||
|     | TypeSystemDefinition TypeSystemDefinition | ||||
|     | TypeSystemExtension TypeSystemExtension | ||||
|     = ExecutableDefinition ExecutableDefinition Location | ||||
|     | TypeSystemDefinition TypeSystemDefinition Location | ||||
|     | TypeSystemExtension TypeSystemExtension Location | ||||
|     deriving (Eq, Show) | ||||
|  | ||||
| -- | Top-level definition of a document, either an operation or a fragment. | ||||
|   | ||||
| @@ -50,7 +50,8 @@ document formatter defs | ||||
|     | Minified <-formatter = Lazy.Text.snoc (mconcat encodeDocument) '\n' | ||||
|   where | ||||
|     encodeDocument = foldr executableDefinition [] defs | ||||
|     executableDefinition (ExecutableDefinition x) acc = definition formatter x : acc | ||||
|     executableDefinition (ExecutableDefinition x _) acc = | ||||
|         definition formatter x : acc | ||||
|     executableDefinition _ acc = acc | ||||
|  | ||||
| -- | Converts a t'ExecutableDefinition' into a string. | ||||
|   | ||||
| @@ -1,5 +1,6 @@ | ||||
| {-# LANGUAGE LambdaCase #-} | ||||
| {-# LANGUAGE OverloadedStrings #-} | ||||
| {-# LANGUAGE RecordWildCards #-} | ||||
|  | ||||
| -- | @GraphQL@ document parser. | ||||
| module Language.GraphQL.AST.Parser | ||||
| @@ -19,7 +20,15 @@ import Language.GraphQL.AST.DirectiveLocation | ||||
|     ) | ||||
| import Language.GraphQL.AST.Document | ||||
| import Language.GraphQL.AST.Lexer | ||||
| import Text.Megaparsec (lookAhead, option, try, (<?>)) | ||||
| import Text.Megaparsec | ||||
|     ( SourcePos(..) | ||||
|     , getSourcePos | ||||
|     , lookAhead | ||||
|     , option | ||||
|     , try | ||||
|     , unPos | ||||
|     , (<?>) | ||||
|     ) | ||||
|  | ||||
| -- | Parser for the GraphQL documents. | ||||
| document :: Parser Document | ||||
| @@ -28,10 +37,30 @@ document = unicodeBOM | ||||
|     *> lexeme (NonEmpty.some definition) | ||||
|  | ||||
| definition :: Parser Definition | ||||
| definition = ExecutableDefinition <$> executableDefinition | ||||
|     <|> TypeSystemDefinition <$> typeSystemDefinition | ||||
|     <|> TypeSystemExtension <$> typeSystemExtension | ||||
| definition = executableDefinition' | ||||
|     <|> typeSystemDefinition' | ||||
|     <|> typeSystemExtension' | ||||
|     <?> "Definition" | ||||
|   where | ||||
|     executableDefinition' = do | ||||
|         location <- getLocation | ||||
|         definition' <- executableDefinition | ||||
|         pure $ ExecutableDefinition definition' location | ||||
|     typeSystemDefinition' = do | ||||
|         location <- getLocation | ||||
|         definition' <- typeSystemDefinition | ||||
|         pure $ TypeSystemDefinition definition' location | ||||
|     typeSystemExtension' = do | ||||
|         location <- getLocation | ||||
|         definition' <- typeSystemExtension | ||||
|         pure $ TypeSystemExtension definition' location | ||||
|  | ||||
| getLocation :: Parser Location | ||||
| getLocation = fromSourcePosition <$> getSourcePos | ||||
|   where | ||||
|     fromSourcePosition SourcePos{..} = | ||||
|         Location (wordFromPosition sourceLine) (wordFromPosition sourceColumn) | ||||
|     wordFromPosition = fromIntegral . unPos | ||||
|  | ||||
| executableDefinition :: Parser ExecutableDefinition | ||||
| executableDefinition = DefinitionOperation <$> operationDefinition | ||||
|   | ||||
		Reference in New Issue
	
	Block a user