graphql-0.9.0.0: Haskell GraphQL implementation

Safe HaskellNone
LanguageHaskell2010

Language.GraphQL.Error

Description

Error handling.

Synopsis

Documentation

parseError :: (Applicative f, Serialize a) => ParseErrorBundle Text Void -> f (Response a) Source #

Wraps a parse error into a list of errors.

type CollectErrsT m = StateT (Resolution m) m Source #

A wrapper to pass error messages around.

data Error Source #

GraphQL error.

Constructors

Error 

Fields

Instances
Eq Error Source # 
Instance details

Defined in Language.GraphQL.Error

Methods

(==) :: Error -> Error -> Bool #

(/=) :: Error -> Error -> Bool #

Show Error Source # 
Instance details

Defined in Language.GraphQL.Error

Methods

showsPrec :: Int -> Error -> ShowS #

show :: Error -> String #

showList :: [Error] -> ShowS #

data Resolution m Source #

Executor context.

Constructors

Resolution 

Fields

data Response a Source #

The server's response describes the result of executing the requested operation if successful, and describes any errors encountered during the request.

Constructors

Response 

Fields

Instances
Eq a => Eq (Response a) Source # 
Instance details

Defined in Language.GraphQL.Error

Methods

(==) :: Response a -> Response a -> Bool #

(/=) :: Response a -> Response a -> Bool #

Show a => Show (Response a) Source # 
Instance details

Defined in Language.GraphQL.Error

Methods

showsPrec :: Int -> Response a -> ShowS #

show :: Response a -> String #

showList :: [Response a] -> ShowS #

type ResponseEventStream m a = ConduitT () (Response a) m () Source #

Each event in the underlying Source Stream triggers execution of the subscription selection set. The results of the execution generate a Response Stream.

addErr :: Monad m => Error -> CollectErrsT m () Source #

Adds an error to the list of errors.

addErrMsg :: (Monad m, Serialize a) => Text -> CollectErrsT m a Source #

Convenience function for just wrapping an error message.

runCollectErrs :: (Monad m, Serialize a) => HashMap Name (Type m) -> CollectErrsT m a -> m (Response a) Source #

Runs the given query computation, but collects the errors into an error list, which is then sent back with the data.

singleError :: Serialize a => Text -> Response a Source #

Constructs a response object containing only the error with the given message.