Handle comments in whitespace
This commit is contained in:
parent
3084b188dd
commit
ec018db73a
@ -1,8 +1,10 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE LambdaCase #-}
|
||||||
module Data.GraphQL.Parser where
|
module Data.GraphQL.Parser where
|
||||||
|
|
||||||
import Prelude hiding (takeWhile)
|
import Prelude hiding (takeWhile)
|
||||||
import Control.Applicative (Alternative, (<|>), empty, many, optional)
|
import Control.Applicative (Alternative, (<|>), empty, many, optional)
|
||||||
|
import Control.Monad (when)
|
||||||
import Data.Char
|
import Data.Char
|
||||||
|
|
||||||
import Data.Text (Text, pack)
|
import Data.Text (Text, pack)
|
||||||
@ -18,6 +20,7 @@ import Data.Attoparsec.Text
|
|||||||
, many1
|
, many1
|
||||||
, manyTill
|
, manyTill
|
||||||
, option
|
, option
|
||||||
|
, peekChar
|
||||||
, satisfy
|
, satisfy
|
||||||
, sepBy
|
, sepBy
|
||||||
, sepBy1
|
, sepBy1
|
||||||
@ -45,8 +48,8 @@ name = tok $ pack <$> many1 (satisfy isAlphaNum)
|
|||||||
-- * Document
|
-- * Document
|
||||||
|
|
||||||
document :: Parser Document
|
document :: Parser Document
|
||||||
document = whiteSpace *>
|
document = whiteSpace
|
||||||
(Document <$> many1 definition)
|
*> (Document <$> many1 definition)
|
||||||
-- Try SelectionSet when no definition
|
-- Try SelectionSet when no definition
|
||||||
<|> (Document . pure
|
<|> (Document . pure
|
||||||
. DefinitionOperation
|
. DefinitionOperation
|
||||||
@ -322,11 +325,8 @@ optempty = option mempty
|
|||||||
-- ** WhiteSpace
|
-- ** WhiteSpace
|
||||||
--
|
--
|
||||||
whiteSpace :: Parser ()
|
whiteSpace :: Parser ()
|
||||||
whiteSpace =
|
whiteSpace = peekChar >>= \case
|
||||||
skipMany (satisfy (\c -> isSpace c || ',' == c || isEndOfLine c))
|
Just c -> if isSpace c || c == ','
|
||||||
|
then anyChar *> whiteSpace
|
||||||
skipComments :: Parser ()
|
else when (c == '#') $ manyTill anyChar endOfLine *> whiteSpace
|
||||||
skipComments = skipMany comment
|
_ -> return ()
|
||||||
|
|
||||||
comment :: Parser Text
|
|
||||||
comment = "#" *> (pack <$> manyTill anyChar endOfLine)
|
|
||||||
|
3
TODO
3
TODO
@ -5,9 +5,8 @@
|
|||||||
- Deal with Location
|
- Deal with Location
|
||||||
|
|
||||||
## Parser
|
## Parser
|
||||||
- Handle comments
|
|
||||||
- Secure Names
|
- Secure Names
|
||||||
- Optimize `name`: `take...`, `T.fold`, ...
|
- Optimize `name` and `whiteSpace`: `take...`, `T.fold`, ...
|
||||||
- Handle escape characters in string literals
|
- Handle escape characters in string literals
|
||||||
- Guard for `on` in `FragmentSpread`
|
- Guard for `on` in `FragmentSpread`
|
||||||
- Tests!
|
- Tests!
|
||||||
|
Loading…
Reference in New Issue
Block a user