2020-07-05 14:36:00 +02:00
|
|
|
{-# LANGUAGE DuplicateRecordFields #-}
|
2016-03-12 00:59:51 +01:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2019-07-19 06:38:54 +02:00
|
|
|
{-# LANGUAGE RecordWildCards #-}
|
2019-09-20 08:47:14 +02:00
|
|
|
|
|
|
|
-- | Error handling.
|
2019-07-07 06:31:53 +02:00
|
|
|
module Language.GraphQL.Error
|
2019-07-14 05:58:05 +02:00
|
|
|
( parseError
|
|
|
|
, CollectErrsT
|
2020-07-05 14:36:00 +02:00
|
|
|
, Error(..)
|
2020-05-27 23:18:35 +02:00
|
|
|
, Resolution(..)
|
2020-07-05 14:36:00 +02:00
|
|
|
, Response(..)
|
2019-07-14 05:58:05 +02:00
|
|
|
, addErr
|
|
|
|
, addErrMsg
|
|
|
|
, runCollectErrs
|
2019-07-23 06:04:33 +02:00
|
|
|
, singleError
|
2019-07-14 05:58:05 +02:00
|
|
|
) where
|
2016-03-12 00:59:51 +01:00
|
|
|
|
2020-05-27 23:18:35 +02:00
|
|
|
import Control.Monad.Trans.State (StateT, modify, runStateT)
|
|
|
|
import Data.HashMap.Strict (HashMap)
|
2020-07-05 14:36:00 +02:00
|
|
|
import Data.Sequence (Seq(..), (|>))
|
|
|
|
import qualified Data.Sequence as Seq
|
2019-07-19 06:38:54 +02:00
|
|
|
import Data.Text (Text)
|
2020-07-05 14:36:00 +02:00
|
|
|
import qualified Data.Text as Text
|
2019-07-19 06:38:54 +02:00
|
|
|
import Data.Void (Void)
|
2020-05-27 23:18:35 +02:00
|
|
|
import Language.GraphQL.AST.Document (Name)
|
2020-07-05 14:36:00 +02:00
|
|
|
import Language.GraphQL.Execute.Coerce
|
2020-05-27 23:18:35 +02:00
|
|
|
import Language.GraphQL.Type.Schema
|
2020-07-05 14:36:00 +02:00
|
|
|
import Prelude hiding (null)
|
2020-02-20 05:16:14 +01:00
|
|
|
import Text.Megaparsec
|
|
|
|
( ParseErrorBundle(..)
|
|
|
|
, PosState(..)
|
|
|
|
, SourcePos(..)
|
|
|
|
, errorOffset
|
|
|
|
, parseErrorTextPretty
|
|
|
|
, reachOffset
|
|
|
|
, unPos
|
|
|
|
)
|
2016-03-12 00:59:51 +01:00
|
|
|
|
2020-06-03 07:20:38 +02:00
|
|
|
-- | Executor context.
|
2020-05-27 23:18:35 +02:00
|
|
|
data Resolution m = Resolution
|
2020-07-05 14:36:00 +02:00
|
|
|
{ errors :: Seq Error
|
2020-05-27 23:18:35 +02:00
|
|
|
, types :: HashMap Name (Type m)
|
|
|
|
}
|
|
|
|
|
2016-03-12 00:59:51 +01:00
|
|
|
-- | Wraps a parse error into a list of errors.
|
2020-07-05 14:36:00 +02:00
|
|
|
parseError :: (Applicative f, Serialize a)
|
|
|
|
=> ParseErrorBundle Text Void
|
|
|
|
-> f (Response a)
|
2019-07-19 06:38:54 +02:00
|
|
|
parseError ParseErrorBundle{..} =
|
2020-07-05 14:36:00 +02:00
|
|
|
pure $ Response null $ fst
|
|
|
|
$ foldl go (Seq.empty, bundlePosState) bundleErrors
|
2019-07-19 06:38:54 +02:00
|
|
|
where
|
2020-07-05 14:36:00 +02:00
|
|
|
errorObject s SourcePos{..} = Error
|
|
|
|
(Text.pack $ init $ parseErrorTextPretty s)
|
|
|
|
(unPos' sourceLine)
|
|
|
|
(unPos' sourceColumn)
|
|
|
|
unPos' = fromIntegral . unPos
|
2019-07-19 06:38:54 +02:00
|
|
|
go (result, state) x =
|
2020-02-20 05:16:14 +01:00
|
|
|
let (_, newState) = reachOffset (errorOffset x) state
|
|
|
|
sourcePosition = pstateSourcePos newState
|
2020-07-05 14:36:00 +02:00
|
|
|
in (result |> errorObject x sourcePosition, newState)
|
2016-03-12 00:59:51 +01:00
|
|
|
|
2019-06-28 11:12:28 +02:00
|
|
|
-- | A wrapper to pass error messages around.
|
2020-05-27 23:18:35 +02:00
|
|
|
type CollectErrsT m = StateT (Resolution m) m
|
2016-03-12 00:59:51 +01:00
|
|
|
|
|
|
|
-- | Adds an error to the list of errors.
|
2020-07-05 14:36:00 +02:00
|
|
|
addErr :: Monad m => Error -> CollectErrsT m ()
|
2020-05-27 23:18:35 +02:00
|
|
|
addErr v = modify appender
|
|
|
|
where
|
2020-07-05 14:36:00 +02:00
|
|
|
appender :: Monad m => Resolution m -> Resolution m
|
|
|
|
appender resolution@Resolution{..} = resolution{ errors = errors |> v }
|
2016-03-12 00:59:51 +01:00
|
|
|
|
2020-07-05 14:36:00 +02:00
|
|
|
makeErrorMessage :: Text -> Error
|
|
|
|
makeErrorMessage s = Error s 0 0
|
2019-07-23 06:04:33 +02:00
|
|
|
|
|
|
|
-- | Constructs a response object containing only the error with the given
|
2020-07-05 14:36:00 +02:00
|
|
|
-- message.
|
|
|
|
singleError :: Serialize a => Text -> Response a
|
|
|
|
singleError message = Response null $ Seq.singleton $ makeErrorMessage message
|
2016-03-12 00:59:51 +01:00
|
|
|
|
|
|
|
-- | Convenience function for just wrapping an error message.
|
2019-06-28 11:12:28 +02:00
|
|
|
addErrMsg :: Monad m => Text -> CollectErrsT m ()
|
2019-07-23 06:04:33 +02:00
|
|
|
addErrMsg = addErr . makeErrorMessage
|
2016-03-12 00:59:51 +01:00
|
|
|
|
2020-07-05 14:36:00 +02:00
|
|
|
-- | @GraphQL@ error.
|
|
|
|
data Error = Error
|
|
|
|
{ message :: Text
|
|
|
|
, line :: Word
|
|
|
|
, column :: Word
|
|
|
|
} deriving (Eq, Show)
|
|
|
|
|
|
|
|
-- | The server\'s response describes the result of executing the requested
|
|
|
|
-- operation if successful, and describes any errors encountered during the
|
|
|
|
-- request.
|
|
|
|
data Response a = Response
|
|
|
|
{ data' :: a
|
|
|
|
, errors :: Seq Error
|
|
|
|
} deriving (Eq, Show)
|
|
|
|
|
2019-06-28 11:12:28 +02:00
|
|
|
-- | Runs the given query computation, but collects the errors into an error
|
2020-07-05 14:36:00 +02:00
|
|
|
-- list, which is then sent back with the data.
|
|
|
|
runCollectErrs :: (Monad m, Serialize a)
|
2020-05-27 23:18:35 +02:00
|
|
|
=> HashMap Name (Type m)
|
2020-07-05 14:36:00 +02:00
|
|
|
-> CollectErrsT m a
|
|
|
|
-> m (Response a)
|
2020-05-27 23:18:35 +02:00
|
|
|
runCollectErrs types' res = do
|
2020-07-05 14:36:00 +02:00
|
|
|
(dat, Resolution{..}) <- runStateT res
|
|
|
|
$ Resolution{ errors = Seq.empty, types = types' }
|
|
|
|
pure $ Response dat errors
|