Return parser error location in a list
An error can have multiple locations which are returned in a listt with key "locations".
This commit is contained in:
@ -19,6 +19,7 @@ module Language.GraphQL.AST.Document
|
||||
, FragmentDefinition(..)
|
||||
, ImplementsInterfaces(..)
|
||||
, InputValueDefinition(..)
|
||||
, Location(..)
|
||||
, Name
|
||||
, NamedType
|
||||
, NonNullType(..)
|
||||
@ -55,6 +56,12 @@ import Language.GraphQL.AST.DirectiveLocation
|
||||
-- | Name.
|
||||
type Name = Text
|
||||
|
||||
-- | Error location, line and column.
|
||||
data Location = Location
|
||||
{ line :: Word
|
||||
, column :: Word
|
||||
} deriving (Eq, Show)
|
||||
|
||||
-- ** Document
|
||||
|
||||
-- | GraphQL document.
|
||||
|
@ -254,19 +254,20 @@ stringValue (Pretty indentation) string =
|
||||
char == '\t' || isNewline char || (char >= '\x0020' && char /= '\x007F')
|
||||
|
||||
tripleQuote = Builder.fromText "\"\"\""
|
||||
start = tripleQuote <> Builder.singleton '\n'
|
||||
end = Builder.fromLazyText (indent indentation) <> tripleQuote
|
||||
newline = Builder.singleton '\n'
|
||||
|
||||
strip = Text.dropWhile isWhiteSpace . Text.dropWhileEnd isWhiteSpace
|
||||
lines' = map Builder.fromText $ Text.split isNewline (Text.replace "\r\n" "\n" $ strip string)
|
||||
encoded [] = oneLine string
|
||||
encoded [_] = oneLine string
|
||||
encoded lines'' = start <> transformLines lines'' <> end
|
||||
transformLines = foldr ((\line acc -> line <> Builder.singleton '\n' <> acc) . transformLine) mempty
|
||||
transformLine line =
|
||||
if Lazy.Text.null (Builder.toLazyText line)
|
||||
then line
|
||||
else Builder.fromLazyText (indent (indentation + 1)) <> line
|
||||
encoded lines'' = tripleQuote <> newline
|
||||
<> transformLines lines''
|
||||
<> Builder.fromLazyText (indent indentation) <> tripleQuote
|
||||
transformLines = foldr transformLine mempty
|
||||
transformLine "" acc = newline <> acc
|
||||
transformLine line' acc
|
||||
= Builder.fromLazyText (indent (indentation + 1))
|
||||
<> line' <> newline <> acc
|
||||
|
||||
escape :: Char -> Builder
|
||||
escape char'
|
||||
|
@ -22,7 +22,7 @@ import qualified Data.Sequence as Seq
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as Text
|
||||
import Data.Void (Void)
|
||||
import Language.GraphQL.AST.Document (Name)
|
||||
import Language.GraphQL.AST (Location(..), Name)
|
||||
import Language.GraphQL.Execute.Coerce
|
||||
import Language.GraphQL.Type.Schema
|
||||
import Prelude hiding (null)
|
||||
@ -51,9 +51,9 @@ parseError ParseErrorBundle{..} =
|
||||
$ foldl go (Seq.empty, bundlePosState) bundleErrors
|
||||
where
|
||||
errorObject s SourcePos{..} = Error
|
||||
(Text.pack $ init $ parseErrorTextPretty s)
|
||||
(unPos' sourceLine)
|
||||
(unPos' sourceColumn)
|
||||
{ message = Text.pack $ init $ parseErrorTextPretty s
|
||||
, locations = [Location (unPos' sourceLine) (unPos' sourceColumn)]
|
||||
}
|
||||
unPos' = fromIntegral . unPos
|
||||
go (result, state) x =
|
||||
let (_, newState) = reachOffset (errorOffset x) state
|
||||
@ -71,7 +71,7 @@ addErr v = modify appender
|
||||
appender resolution@Resolution{..} = resolution{ errors = errors |> v }
|
||||
|
||||
makeErrorMessage :: Text -> Error
|
||||
makeErrorMessage s = Error s 0 0
|
||||
makeErrorMessage s = Error s []
|
||||
|
||||
-- | Constructs a response object containing only the error with the given
|
||||
-- message.
|
||||
@ -85,8 +85,7 @@ addErrMsg errorMessage = (addErr . makeErrorMessage) errorMessage >> pure null
|
||||
-- | @GraphQL@ error.
|
||||
data Error = Error
|
||||
{ message :: Text
|
||||
, line :: Word
|
||||
, column :: Word
|
||||
, locations :: [Location]
|
||||
} deriving (Eq, Show)
|
||||
|
||||
-- | The server\'s response describes the result of executing the requested
|
||||
|
Reference in New Issue
Block a user