This commit is contained in:
Danny Navarro 2015-09-18 16:29:21 +02:00
parent 4f4e31805a
commit cb9977141d

View File

@ -1,6 +1,5 @@
{-# LANGUAGE CPP #-} {-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
module Data.GraphQL.Parser where module Data.GraphQL.Parser where
import Prelude hiding (takeWhile) import Prelude hiding (takeWhile)
@ -12,6 +11,8 @@ import Data.Monoid (Monoid, mempty)
import Control.Applicative ((<|>), empty, many, optional) import Control.Applicative ((<|>), empty, many, optional)
import Control.Monad (when) import Control.Monad (when)
import Data.Char import Data.Char
import Data.Foldable (traverse_)
import Data.Text (Text, append) import Data.Text (Text, append)
import Data.Attoparsec.Text import Data.Attoparsec.Text
( Parser ( Parser
@ -323,8 +324,7 @@ optempty = option mempty
-- ** WhiteSpace -- ** WhiteSpace
-- --
whiteSpace :: Parser () whiteSpace :: Parser ()
whiteSpace = peekChar >>= \case whiteSpace = peekChar >>= traverse_ (\c ->
Just c -> if isSpace c || c == ',' if isSpace c || c == ','
then anyChar *> whiteSpace then anyChar *> whiteSpace
else when (c == '#') $ manyTill anyChar endOfLine *> whiteSpace else when (c == '#') $ manyTill anyChar endOfLine *> whiteSpace)
_ -> return ()