Deprecate internal error generation functions
The functions generating errors in the executor should be changed anyway when we provide better error messages from the executor, with the error location and response path. So public definitions of these functions are deprecated now and they are replaced by more generic functions in the executor code.
This commit is contained in:
@ -3,23 +3,34 @@
|
||||
obtain one at https://mozilla.org/MPL/2.0/. -}
|
||||
|
||||
{-# LANGUAGE DuplicateRecordFields #-}
|
||||
{-# LANGUAGE ExplicitForAll #-}
|
||||
{-# LANGUAGE NamedFieldPuns #-}
|
||||
|
||||
module Language.GraphQL.Execute.Internal
|
||||
( addError
|
||||
, singleError
|
||||
) where
|
||||
|
||||
import Control.Monad.Trans.State (modify)
|
||||
import Control.Monad.Catch (MonadCatch)
|
||||
import Data.Sequence ((|>))
|
||||
import Language.GraphQL.Error
|
||||
import Data.Text (Text)
|
||||
import Language.GraphQL.Execute.Coerce
|
||||
import Language.GraphQL.Error
|
||||
( CollectErrsT
|
||||
, Error(..)
|
||||
, Resolution(..)
|
||||
, Response(..)
|
||||
)
|
||||
import Prelude hiding (null)
|
||||
|
||||
addError :: (Serialize a, MonadCatch m) => Error -> CollectErrsT m a
|
||||
addError error' = modify appender >> pure null
|
||||
addError :: MonadCatch m => forall a. a -> Error -> CollectErrsT m a
|
||||
addError returnValue error' = modify appender >> pure returnValue
|
||||
where
|
||||
appender :: Resolution m -> Resolution m
|
||||
appender resolution@Resolution{ errors } = resolution
|
||||
{ errors = errors |> error'
|
||||
}
|
||||
|
||||
singleError :: Serialize b => forall a. Text -> Either a (Response b)
|
||||
singleError message = Right $ Response null $ pure $ Error message [] []
|
||||
|
Reference in New Issue
Block a user