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:
parent
b2d473de8d
commit
c9e265f72c
@ -7,8 +7,13 @@ and this project adheres to
|
|||||||
[Haskell Package Versioning Policy](https://pvp.haskell.org/).
|
[Haskell Package Versioning Policy](https://pvp.haskell.org/).
|
||||||
|
|
||||||
## [Unreleased]
|
## [Unreleased]
|
||||||
|
## Fixed
|
||||||
|
- Location of a parse error is returned in a singleton array with key
|
||||||
|
`locations`.
|
||||||
|
|
||||||
## Added
|
## Added
|
||||||
- `AST` reexports `AST.Parser`.
|
- `AST` reexports `AST.Parser`.
|
||||||
|
- `AST.Document.Location` is a token location as a line and column pair.
|
||||||
- `Execute` reexports `Execute.Coerce`.
|
- `Execute` reexports `Execute.Coerce`.
|
||||||
- `Error.Error` is an error representation with a message and source location.
|
- `Error.Error` is an error representation with a message and source location.
|
||||||
- `Error.Response` represents a result of running a GraphQL query.
|
- `Error.Response` represents a result of running a GraphQL query.
|
||||||
@ -25,6 +30,10 @@ and this project adheres to
|
|||||||
- `Execute.execute` takes an additional argument, a possible operation name.
|
- `Execute.execute` takes an additional argument, a possible operation name.
|
||||||
- `Error` module was changed to work with dedicated types for errors and the
|
- `Error` module was changed to work with dedicated types for errors and the
|
||||||
response instead of JSON.
|
response instead of JSON.
|
||||||
|
- `graphqlSubs` takes an additional argument, the operation name. The type of
|
||||||
|
variable names is changed back to JSON since it is a common format and it
|
||||||
|
saves additional conversions. Custom format still can be used with the
|
||||||
|
underlying functions (in the `Execute` module).
|
||||||
|
|
||||||
## Removed
|
## Removed
|
||||||
- `Type.Out.Resolver`: It is an unneeded layer of complexity. Resolvers are a
|
- `Type.Out.Resolver`: It is an unneeded layer of complexity. Resolvers are a
|
||||||
|
@ -8,6 +8,7 @@ module Language.GraphQL
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import qualified Data.Aeson as Aeson
|
import qualified Data.Aeson as Aeson
|
||||||
|
import qualified Data.Aeson.Types as Aeson
|
||||||
import qualified Data.Sequence as Seq
|
import qualified Data.Sequence as Seq
|
||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import Language.GraphQL.AST
|
import Language.GraphQL.AST
|
||||||
@ -41,13 +42,16 @@ graphqlSubs schema operationName variableValues document' =
|
|||||||
pure $ Aeson.object [("data", data'')]
|
pure $ Aeson.object [("data", data'')]
|
||||||
formatResponse (Response data'' errors') = pure $ Aeson.object
|
formatResponse (Response data'' errors') = pure $ Aeson.object
|
||||||
[ ("data", data'')
|
[ ("data", data'')
|
||||||
, ("errors", Aeson.toJSON $ toJSON <$> errors')
|
, ("errors", Aeson.toJSON $ fromError <$> errors')
|
||||||
]
|
]
|
||||||
toJSON Error{ line = 0, column = 0, ..} =
|
fromError Error{ locations = [], ..} =
|
||||||
Aeson.object [("message", Aeson.toJSON message)]
|
Aeson.object [("message", Aeson.toJSON message)]
|
||||||
toJSON Error{..} = Aeson.object
|
fromError Error{..} = Aeson.object
|
||||||
[ ("message", Aeson.toJSON message)
|
[ ("message", Aeson.toJSON message)
|
||||||
, ("line", Aeson.toJSON line)
|
, ("locations", Aeson.listValue fromLocation locations)
|
||||||
|
]
|
||||||
|
fromLocation Location{..} = Aeson.object
|
||||||
|
[ ("line", Aeson.toJSON line)
|
||||||
, ("column", Aeson.toJSON column)
|
, ("column", Aeson.toJSON column)
|
||||||
]
|
]
|
||||||
executeRequest = execute schema operationName variableValues
|
executeRequest = execute schema operationName variableValues
|
||||||
|
@ -19,6 +19,7 @@ module Language.GraphQL.AST.Document
|
|||||||
, FragmentDefinition(..)
|
, FragmentDefinition(..)
|
||||||
, ImplementsInterfaces(..)
|
, ImplementsInterfaces(..)
|
||||||
, InputValueDefinition(..)
|
, InputValueDefinition(..)
|
||||||
|
, Location(..)
|
||||||
, Name
|
, Name
|
||||||
, NamedType
|
, NamedType
|
||||||
, NonNullType(..)
|
, NonNullType(..)
|
||||||
@ -55,6 +56,12 @@ import Language.GraphQL.AST.DirectiveLocation
|
|||||||
-- | Name.
|
-- | Name.
|
||||||
type Name = Text
|
type Name = Text
|
||||||
|
|
||||||
|
-- | Error location, line and column.
|
||||||
|
data Location = Location
|
||||||
|
{ line :: Word
|
||||||
|
, column :: Word
|
||||||
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
-- ** Document
|
-- ** Document
|
||||||
|
|
||||||
-- | GraphQL document.
|
-- | GraphQL document.
|
||||||
|
@ -254,19 +254,20 @@ stringValue (Pretty indentation) string =
|
|||||||
char == '\t' || isNewline char || (char >= '\x0020' && char /= '\x007F')
|
char == '\t' || isNewline char || (char >= '\x0020' && char /= '\x007F')
|
||||||
|
|
||||||
tripleQuote = Builder.fromText "\"\"\""
|
tripleQuote = Builder.fromText "\"\"\""
|
||||||
start = tripleQuote <> Builder.singleton '\n'
|
newline = Builder.singleton '\n'
|
||||||
end = Builder.fromLazyText (indent indentation) <> tripleQuote
|
|
||||||
|
|
||||||
strip = Text.dropWhile isWhiteSpace . Text.dropWhileEnd isWhiteSpace
|
strip = Text.dropWhile isWhiteSpace . Text.dropWhileEnd isWhiteSpace
|
||||||
lines' = map Builder.fromText $ Text.split isNewline (Text.replace "\r\n" "\n" $ strip string)
|
lines' = map Builder.fromText $ Text.split isNewline (Text.replace "\r\n" "\n" $ strip string)
|
||||||
encoded [] = oneLine string
|
encoded [] = oneLine string
|
||||||
encoded [_] = oneLine string
|
encoded [_] = oneLine string
|
||||||
encoded lines'' = start <> transformLines lines'' <> end
|
encoded lines'' = tripleQuote <> newline
|
||||||
transformLines = foldr ((\line acc -> line <> Builder.singleton '\n' <> acc) . transformLine) mempty
|
<> transformLines lines''
|
||||||
transformLine line =
|
<> Builder.fromLazyText (indent indentation) <> tripleQuote
|
||||||
if Lazy.Text.null (Builder.toLazyText line)
|
transformLines = foldr transformLine mempty
|
||||||
then line
|
transformLine "" acc = newline <> acc
|
||||||
else Builder.fromLazyText (indent (indentation + 1)) <> line
|
transformLine line' acc
|
||||||
|
= Builder.fromLazyText (indent (indentation + 1))
|
||||||
|
<> line' <> newline <> acc
|
||||||
|
|
||||||
escape :: Char -> Builder
|
escape :: Char -> Builder
|
||||||
escape char'
|
escape char'
|
||||||
|
@ -22,7 +22,7 @@ import qualified Data.Sequence as Seq
|
|||||||
import Data.Text (Text)
|
import Data.Text (Text)
|
||||||
import qualified Data.Text as Text
|
import qualified Data.Text as Text
|
||||||
import Data.Void (Void)
|
import Data.Void (Void)
|
||||||
import Language.GraphQL.AST.Document (Name)
|
import Language.GraphQL.AST (Location(..), Name)
|
||||||
import Language.GraphQL.Execute.Coerce
|
import Language.GraphQL.Execute.Coerce
|
||||||
import Language.GraphQL.Type.Schema
|
import Language.GraphQL.Type.Schema
|
||||||
import Prelude hiding (null)
|
import Prelude hiding (null)
|
||||||
@ -51,9 +51,9 @@ parseError ParseErrorBundle{..} =
|
|||||||
$ foldl go (Seq.empty, bundlePosState) bundleErrors
|
$ foldl go (Seq.empty, bundlePosState) bundleErrors
|
||||||
where
|
where
|
||||||
errorObject s SourcePos{..} = Error
|
errorObject s SourcePos{..} = Error
|
||||||
(Text.pack $ init $ parseErrorTextPretty s)
|
{ message = Text.pack $ init $ parseErrorTextPretty s
|
||||||
(unPos' sourceLine)
|
, locations = [Location (unPos' sourceLine) (unPos' sourceColumn)]
|
||||||
(unPos' sourceColumn)
|
}
|
||||||
unPos' = fromIntegral . unPos
|
unPos' = fromIntegral . unPos
|
||||||
go (result, state) x =
|
go (result, state) x =
|
||||||
let (_, newState) = reachOffset (errorOffset x) state
|
let (_, newState) = reachOffset (errorOffset x) state
|
||||||
@ -71,7 +71,7 @@ addErr v = modify appender
|
|||||||
appender resolution@Resolution{..} = resolution{ errors = errors |> v }
|
appender resolution@Resolution{..} = resolution{ errors = errors |> v }
|
||||||
|
|
||||||
makeErrorMessage :: Text -> Error
|
makeErrorMessage :: Text -> Error
|
||||||
makeErrorMessage s = Error s 0 0
|
makeErrorMessage s = Error s []
|
||||||
|
|
||||||
-- | Constructs a response object containing only the error with the given
|
-- | Constructs a response object containing only the error with the given
|
||||||
-- message.
|
-- message.
|
||||||
@ -85,8 +85,7 @@ addErrMsg errorMessage = (addErr . makeErrorMessage) errorMessage >> pure null
|
|||||||
-- | @GraphQL@ error.
|
-- | @GraphQL@ error.
|
||||||
data Error = Error
|
data Error = Error
|
||||||
{ message :: Text
|
{ message :: Text
|
||||||
, line :: Word
|
, locations :: [Location]
|
||||||
, column :: Word
|
|
||||||
} deriving (Eq, Show)
|
} deriving (Eq, Show)
|
||||||
|
|
||||||
-- | The server\'s response describes the result of executing the requested
|
-- | The server\'s response describes the result of executing the requested
|
||||||
|
@ -15,6 +15,6 @@ import Test.Hspec ( Spec
|
|||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = describe "singleError" $
|
spec = describe "singleError" $
|
||||||
it "constructs an error with the given message" $
|
it "constructs an error with the given message" $
|
||||||
let errors'' = Seq.singleton $ Error "Message." 0 0
|
let errors'' = Seq.singleton $ Error "Message." []
|
||||||
expected = Response Aeson.Null errors''
|
expected = Response Aeson.Null errors''
|
||||||
in singleError "Message." `shouldBe` expected
|
in singleError "Message." `shouldBe` expected
|
||||||
|
Loading…
Reference in New Issue
Block a user