Add "extend symbol" lexer to parse extensions

This commit is contained in:
Eugen Wissner 2020-01-17 12:22:29 +01:00
parent ba710a3c96
commit 3ef27f9d11
5 changed files with 14 additions and 2 deletions

View File

@ -20,6 +20,8 @@ and this project adheres to
- Rename `AST.OperationSelectionSet` to `AST.Document.SelectionSet`.
- Make `Schema.Subs` a `Data.HashMap.Strict` (was a function
`key -> Maybe value` before).
- Make `AST.Lexer.at` a text (symbol) parser. It was a char before and is
`symbol "@"` now.
### Removed
- `AST.Field`, `AST.InlineFragment` and `AST.FragmentSpread`.

View File

@ -8,7 +8,7 @@ module Language.GraphQL.AST.Document
( Alias
, Argument(..)
, ArgumentsDefinition(..)
, Definition(ExecutableDefinition, TypeSystemDefinition)
, Definition(..)
, Description(..)
, Directive(..)
, Document
@ -26,6 +26,7 @@ module Language.GraphQL.AST.Document
, OperationType(..)
, OperationTypeDefinition(..)
, OperationTypeDefinitions
, SchemaExtension(..)
, Selection(..)
, SelectionSet
, SelectionSetOpt
@ -34,6 +35,7 @@ module Language.GraphQL.AST.Document
, TypeDefinition(..)
, TypeExtension(..)
, TypeSystemDefinition(..)
, TypeSystemExtension(..)
, UnionMemberTypes(..)
, Value(..)
, VariableDefinition(..)

View File

@ -15,6 +15,7 @@ module Language.GraphQL.AST.Lexer
, dollar
, comment
, equals
, extend
, integer
, float
, lexeme
@ -31,6 +32,7 @@ module Language.GraphQL.AST.Lexer
import Control.Applicative (Alternative(..), liftA2)
import Data.Char (chr, digitToInt, isAsciiLower, isAsciiUpper, ord)
import Data.Foldable (foldl')
import Data.Functor (($>))
import Data.List (dropWhileEnd)
import Data.Proxy (Proxy(..))
import Data.Void (Void)
@ -217,3 +219,7 @@ escapeSequence = do
-- | Parser for the "Byte Order Mark".
unicodeBOM :: Parser ()
unicodeBOM = optional (char '\xfeff') >> pure ()
-- | Parses "extend" followed by a 'symbol'. It is used by schema extensions.
extend :: Text -> Parser ()
extend token = symbol "extend" $> extend token >> pure ()

View File

@ -215,7 +215,7 @@ schemaDefinition = SchemaDefinition
<*> operationTypeDefinitions
<?> "SchemaDefinition"
where
operationTypeDefinitions = braces $ NonEmpty.some operationTypeDefinition
operationTypeDefinitions = braces $ NonEmpty.some operationTypeDefinition
operationTypeDefinition :: Parser OperationTypeDefinition
operationTypeDefinition = OperationTypeDefinition

View File

@ -87,6 +87,8 @@ spec = describe "Lexer" $ do
parse blockString "" [r|""""""|] `shouldParse` ""
it "lexes ampersand" $
parse amp "" "&" `shouldParse` "&"
it "lexes schema extensions" $
parse (extend "schema") "" `shouldSucceedOn` "extend schema"
runBetween :: (Parser () -> Parser ()) -> Text -> Either (ParseErrorBundle Text Void) ()
runBetween parser = parse (parser $ pure ()) ""