Deprecate unused functions from the old executor
This commit is contained in:
		| @@ -44,12 +44,6 @@ import Text.Megaparsec | ||||
|     , unPos | ||||
|     ) | ||||
|  | ||||
| -- | Executor context. | ||||
| data Resolution m = Resolution | ||||
|     { errors :: Seq Error | ||||
|     , types :: HashMap Name (Schema.Type m) | ||||
|     } | ||||
|  | ||||
| -- | Wraps a parse error into a list of errors. | ||||
| parseError :: (Applicative f, Serialize a) | ||||
|     => ParseErrorBundle Text Void | ||||
| @@ -69,32 +63,6 @@ parseError ParseErrorBundle{..}  = | ||||
|             sourcePosition = pstateSourcePos newState | ||||
|          in (result |> errorObject x sourcePosition, newState) | ||||
|  | ||||
| -- | A wrapper to pass error messages around. | ||||
| type CollectErrsT m = StateT (Resolution m) m | ||||
|  | ||||
| -- | Adds an error to the list of errors. | ||||
| {-# DEPRECATED #-} | ||||
| addErr :: Monad m => Error -> CollectErrsT m () | ||||
| addErr v = modify appender | ||||
|   where | ||||
|     appender :: Monad m => Resolution m -> Resolution m | ||||
|     appender resolution@Resolution{..} = resolution{ errors = errors |> v } | ||||
|  | ||||
| {-# DEPRECATED #-} | ||||
| makeErrorMessage :: Text -> Error | ||||
| makeErrorMessage s = Error s [] [] | ||||
|  | ||||
| -- | Constructs a response object containing only the error with the given | ||||
| -- message. | ||||
| {-# DEPRECATED #-} | ||||
| singleError :: Serialize a => Text -> Response a | ||||
| singleError message = Response null $ Seq.singleton $ Error message [] [] | ||||
|  | ||||
| -- | Convenience function for just wrapping an error message. | ||||
| {-# DEPRECATED #-} | ||||
| addErrMsg :: (Monad m, Serialize a) => Text -> CollectErrsT m a | ||||
| addErrMsg errorMessage = (addErr . makeErrorMessage) errorMessage >> pure null | ||||
|  | ||||
| -- | If an error can be associated to a particular field in the GraphQL result, | ||||
| -- it must contain an entry with the key path that details the path of the | ||||
| -- response field which experienced the error. This allows clients to identify | ||||
| @@ -133,8 +101,13 @@ instance Show ResolverException where | ||||
|  | ||||
| instance Exception ResolverException | ||||
|  | ||||
| -- * Deprecated | ||||
|  | ||||
| -- | Runs the given query computation, but collects the errors into an error | ||||
| -- list, which is then sent back with the data. | ||||
| -- | ||||
| -- /runCollectErrs was part of the old executor and isn't used anymore, it will | ||||
| -- be deprecated in the future and removed./ | ||||
| runCollectErrs :: (Monad m, Serialize a) | ||||
|     => HashMap Name (Schema.Type m) | ||||
|     -> CollectErrsT m a | ||||
| @@ -143,3 +116,41 @@ runCollectErrs types' res = do | ||||
|     (dat, Resolution{..}) <- runStateT res | ||||
|         $ Resolution{ errors = Seq.empty, types = types' } | ||||
|     pure $ Response dat errors | ||||
|  | ||||
| -- | Executor context. | ||||
| -- | ||||
| -- /Resolution was part of the old executor and isn't used anymore, it will be | ||||
| -- deprecated in the future and removed./ | ||||
| data Resolution m = Resolution | ||||
|     { errors :: Seq Error | ||||
|     , types :: HashMap Name (Schema.Type m) | ||||
|     } | ||||
|  | ||||
| -- | A wrapper to pass error messages around. | ||||
| -- | ||||
| -- /CollectErrsT was part of the old executor and isn't used anymore, it will be | ||||
| -- deprecated in the future and removed./ | ||||
| type CollectErrsT m = StateT (Resolution m) m | ||||
|  | ||||
| -- | Adds an error to the list of errors. | ||||
| {-# DEPRECATED #-} | ||||
| addErr :: Monad m => Error -> CollectErrsT m () | ||||
| addErr v = modify appender | ||||
|   where | ||||
|     appender :: Monad m => Resolution m -> Resolution m | ||||
|     appender resolution@Resolution{..} = resolution{ errors = errors |> v } | ||||
|  | ||||
| {-# DEPRECATED #-} | ||||
| makeErrorMessage :: Text -> Error | ||||
| makeErrorMessage s = Error s [] [] | ||||
|  | ||||
| -- | Constructs a response object containing only the error with the given | ||||
| -- message. | ||||
| {-# DEPRECATED #-} | ||||
| singleError :: Serialize a => Text -> Response a | ||||
| singleError message = Response null $ Seq.singleton $ Error message [] [] | ||||
|  | ||||
| -- | Convenience function for just wrapping an error message. | ||||
| {-# DEPRECATED #-} | ||||
| addErrMsg :: (Monad m, Serialize a) => Text -> CollectErrsT m a | ||||
| addErrMsg errorMessage = (addErr . makeErrorMessage) errorMessage >> pure null | ||||
|   | ||||
| @@ -9,10 +9,11 @@ | ||||
| {-# LANGUAGE ViewPatterns #-} | ||||
| {-# LANGUAGE TypeApplications #-} | ||||
|  | ||||
| -- | This module provides functions to execute a @GraphQL@ request. | ||||
| module Language.GraphQL.Execute | ||||
|    ( module Language.GraphQL.Execute.Coerce | ||||
|    , execute | ||||
|    ) where | ||||
|     ( execute | ||||
|     , module Language.GraphQL.Execute.Coerce | ||||
|     ) where | ||||
|  | ||||
| import Conduit (mapMC, (.|)) | ||||
| import Control.Arrow (left) | ||||
| @@ -179,6 +180,7 @@ instance Exception ResultCoercionException where | ||||
|     toException = resultExceptionToException | ||||
|     fromException = resultExceptionFromException | ||||
|  | ||||
| -- | Query error types. | ||||
| data QueryError | ||||
|     = OperationNameRequired | ||||
|     | OperationNotFound String | ||||
| @@ -217,6 +219,12 @@ queryError (UnknownInputType variableDefinition) = | ||||
|             ] | ||||
|      in Error{ message = queryErrorMessage, locations = [location], path = [] } | ||||
|  | ||||
| -- | The substitution is applied to the document, and the resolvers are applied | ||||
| -- to the resulting fields. The operation name can be used if the document | ||||
| -- defines multiple root operations. | ||||
| -- | ||||
| -- Returns the result of the query against the schema wrapped in a /data/ | ||||
| -- field, or errors wrapped in an /errors/ field. | ||||
| execute :: (MonadCatch m, VariableValue a, Serialize b) | ||||
|     => Schema m -- ^ Resolvers. | ||||
|     -> Maybe Text -- ^ Operation name. | ||||
|   | ||||
| @@ -58,6 +58,7 @@ import qualified Language.GraphQL.Type.Definition as Definition | ||||
| import qualified Language.GraphQL.Type.Internal as Type | ||||
| import Numeric (showFloat) | ||||
|  | ||||
| -- | Associates a fragment name with a list of 'Field's. | ||||
| data Replacement m = Replacement | ||||
|     { variableValues :: Type.Subs | ||||
|     , fragmentDefinitions :: HashMap Full.Name Full.FragmentDefinition | ||||
| @@ -92,9 +93,11 @@ instance MonadCatch m => MonadCatch (TransformT m) where | ||||
| asks :: Monad m => forall a. (Replacement m -> a) -> TransformT m a | ||||
| asks = TransformT . Reader.asks | ||||
|  | ||||
| -- | GraphQL has 3 operation types: queries, mutations and subscribtions. | ||||
| data Operation m | ||||
|     = Operation Full.OperationType (Seq (Selection m)) Full.Location | ||||
|  | ||||
| -- | Field or inlined fragment. | ||||
| data Selection m | ||||
|     = FieldSelection (Field m) | ||||
|     | FragmentSelection (Fragment m) | ||||
| @@ -142,6 +145,7 @@ instance Show Input where | ||||
|             concat [Text.unpack key, ": ", show value] : accumulator | ||||
|     show variableValue = show variableValue | ||||
|  | ||||
| -- | Extracts operations and fragment definitions of the document. | ||||
| document :: Full.Document | ||||
|     -> ([Full.OperationDefinition], HashMap Full.Name Full.FragmentDefinition) | ||||
| document = foldr filterOperation ([], HashMap.empty) | ||||
| @@ -154,6 +158,8 @@ document = foldr filterOperation ([], HashMap.empty) | ||||
|             HashMap.insert fragmentName fragmentDefinition <$> accumulator | ||||
|     filterOperation _ accumulator = accumulator -- Type system definitions. | ||||
|  | ||||
| -- | Rewrites the original syntax tree into an intermediate representation used | ||||
| -- for the query execution. | ||||
| transform :: Monad m => Full.OperationDefinition -> TransformT m (Operation m) | ||||
| transform (Full.OperationDefinition operationType _ _ _ selectionSet' operationLocation) = do | ||||
|     transformedSelections <- selectionSet selectionSet' | ||||
| @@ -177,7 +183,7 @@ selection (Full.FieldSelection field') = | ||||
| selection (Full.FragmentSpreadSelection fragmentSpread') = | ||||
|     maybeToSelectionSet FragmentSelection $ fragmentSpread fragmentSpread' | ||||
| selection (Full.InlineFragmentSelection inlineFragment') = | ||||
|    either id (pure . FragmentSelection) <$> inlineFragment inlineFragment' | ||||
|     either id (pure . FragmentSelection) <$> inlineFragment inlineFragment' | ||||
|  | ||||
| maybeToSelectionSet :: Monad m | ||||
|     => forall a | ||||
|   | ||||
		Reference in New Issue
	
	Block a user