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
|
|
|
|
, addErr
|
|
|
|
, addErrMsg
|
|
|
|
, runCollectErrs
|
|
|
|
, runAppendErrs
|
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
|
|
|
|
|
|
|
import qualified Data.Aeson as Aeson
|
2019-07-19 06:38:54 +02:00
|
|
|
import Data.Text (Text)
|
|
|
|
import Data.Void (Void)
|
2019-06-28 11:12:28 +02:00
|
|
|
import Control.Monad.Trans.Class (lift)
|
|
|
|
import Control.Monad.Trans.State ( StateT
|
|
|
|
, modify
|
|
|
|
, runStateT
|
|
|
|
)
|
2019-07-19 06:38:54 +02:00
|
|
|
import Text.Megaparsec ( ParseErrorBundle(..)
|
|
|
|
, SourcePos(..)
|
|
|
|
, errorOffset
|
|
|
|
, parseErrorTextPretty
|
|
|
|
, reachOffset
|
|
|
|
, unPos
|
|
|
|
)
|
2016-03-12 00:59:51 +01:00
|
|
|
|
|
|
|
-- | Wraps a parse error into a list of errors.
|
2019-07-19 06:38:54 +02:00
|
|
|
parseError :: Applicative f => ParseErrorBundle Text Void -> f Aeson.Value
|
|
|
|
parseError ParseErrorBundle{..} =
|
|
|
|
pure $ Aeson.object [("errors", Aeson.toJSON $ fst $ foldl go ([], bundlePosState) bundleErrors)]
|
|
|
|
where
|
|
|
|
errorObject s SourcePos{..} = Aeson.object
|
|
|
|
[ ("message", Aeson.toJSON $ init $ parseErrorTextPretty s)
|
|
|
|
, ("line", Aeson.toJSON $ unPos sourceLine)
|
|
|
|
, ("column", Aeson.toJSON $ unPos sourceColumn)
|
|
|
|
]
|
|
|
|
go (result, state) x =
|
|
|
|
let (sourcePosition, _, newState) = reachOffset (errorOffset x) state
|
|
|
|
in (errorObject x sourcePosition : result, newState)
|
2016-03-12 00:59:51 +01:00
|
|
|
|
2019-06-28 11:12:28 +02:00
|
|
|
-- | A wrapper to pass error messages around.
|
|
|
|
type CollectErrsT m = StateT [Aeson.Value] m
|
2016-03-12 00:59:51 +01:00
|
|
|
|
|
|
|
-- | Adds an error to the list of errors.
|
2019-06-28 11:12:28 +02:00
|
|
|
addErr :: Monad m => Aeson.Value -> CollectErrsT m ()
|
|
|
|
addErr v = modify (v :)
|
2016-03-12 00:59:51 +01:00
|
|
|
|
2019-07-23 06:04:33 +02:00
|
|
|
makeErrorMessage :: Text -> Aeson.Value
|
|
|
|
makeErrorMessage s = Aeson.object [("message", Aeson.toJSON s)]
|
|
|
|
|
|
|
|
-- | Constructs a response object containing only the error with the given
|
|
|
|
-- message.
|
|
|
|
singleError :: Text -> Aeson.Value
|
|
|
|
singleError message = Aeson.object
|
|
|
|
[ ("errors", Aeson.toJSON [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
|
|
|
|
2019-06-28 11:12:28 +02:00
|
|
|
-- | Appends the given list of errors to the current list of errors.
|
|
|
|
appendErrs :: Monad m => [Aeson.Value] -> CollectErrsT m ()
|
|
|
|
appendErrs errs = modify (errs ++)
|
|
|
|
|
|
|
|
-- | Runs the given query computation, but collects the errors into an error
|
|
|
|
-- list, which is then sent back with the data.
|
|
|
|
runCollectErrs :: Monad m => CollectErrsT m Aeson.Value -> m Aeson.Value
|
|
|
|
runCollectErrs res = do
|
|
|
|
(dat, errs) <- runStateT res []
|
|
|
|
if null errs
|
|
|
|
then return $ Aeson.object [("data", dat)]
|
|
|
|
else return $ Aeson.object [("data", dat), ("errors", Aeson.toJSON $ reverse errs)]
|
|
|
|
|
|
|
|
-- | Runs the given computation, collecting the errors and appending them
|
|
|
|
-- to the previous list of errors.
|
|
|
|
runAppendErrs :: Monad m => CollectErrsT m a -> CollectErrsT m a
|
|
|
|
runAppendErrs f = do
|
|
|
|
(v, errs) <- lift $ runStateT f []
|
|
|
|
appendErrs errs
|
|
|
|
return v
|