graphql-api-0.4.0: GraphQL API

Safe HaskellNone
LanguageHaskell2010

GraphQL.Internal.Resolver

Description

 
Synopsis

Documentation

data ResolverError Source #

Constructors

SchemaError SchemaError

There was a problem in the schema. Server-side problem.

FieldNotFoundError Name

Couldn't find the requested field in the object. A client-side problem.

ValueMissing Name

No value provided for name, and no default specified. Client-side problem.

InvalidValue Name Text

Could not translate value into Haskell. Probably a client-side problem.

ValidationError ValidationErrors

Found validation errors when we tried to merge fields.

SubSelectionOnLeaf (SelectionSetByType Value)

Tried to get subselection of leaf field.

MissingSelectionSet

Tried to treat an object as a leaf.

HandlerError Text

Error from handler

class HasResolver m a where Source #

Associated Types

type Handler m a Source #

Instances
Applicative m => HasResolver m Bool Source # 
Instance details

Defined in GraphQL.Internal.Resolver

Associated Types

type Handler m Bool :: Type Source #

Applicative m => HasResolver m Text Source # 
Instance details

Defined in GraphQL.Internal.Resolver

Associated Types

type Handler m Text :: Type Source #

Applicative m => HasResolver m Double Source # 
Instance details

Defined in GraphQL.Internal.Resolver

Associated Types

type Handler m Double :: Type Source #

Applicative m => HasResolver m Int32 Source # 
Instance details

Defined in GraphQL.Internal.Resolver

Associated Types

type Handler m Int32 :: Type Source #

(HasResolver m hg, Monad m) => HasResolver m (Maybe hg :: Type) Source # 
Instance details

Defined in GraphQL.Internal.Resolver

Associated Types

type Handler m (Maybe hg) :: Type Source #

(Monad m, Applicative m, HasResolver m hg) => HasResolver m (List hg :: Type) Source # 
Instance details

Defined in GraphQL.Internal.Resolver

Associated Types

type Handler m (List hg) :: Type Source #

(Monad m, KnownSymbol unionName, RunUnion m (Union unionName objects) objects) => HasResolver m (Union unionName objects :: Type) Source # 
Instance details

Defined in GraphQL.Internal.Resolver

Associated Types

type Handler m (Union unionName objects) :: Type Source #

Methods

resolve :: Handler m (Union unionName objects) -> Maybe (SelectionSetByType Value) -> m (Result Value) Source #

(Applicative m, GraphQLEnum enum) => HasResolver m (Enum ksN enum :: Type) Source # 
Instance details

Defined in GraphQL.Internal.Resolver

Associated Types

type Handler m (Enum ksN enum) :: Type Source #

Methods

resolve :: Handler m (Enum ksN enum) -> Maybe (SelectionSetByType Value) -> m (Result Value) Source #

(RunFields m (RunFieldsType m fields), HasObjectDefinition (Object typeName interfaces fields), Monad m) => HasResolver m (Object typeName interfaces fields :: Type) Source # 
Instance details

Defined in GraphQL.Internal.Resolver

Associated Types

type Handler m (Object typeName interfaces fields) :: Type Source #

Methods

resolve :: Handler m (Object typeName interfaces fields) -> Maybe (SelectionSetByType Value) -> m (Result Value) Source #

type OperationResolverConstraint m fields typeName interfaces = (RunFields m (RunFieldsType m fields), HasObjectDefinition (Object typeName interfaces fields), Monad m) Source #

data a :<> b infixr 8 Source #

Object field separation operator.

Use this to provide handlers for fields of an object.

Say you had the following GraphQL type with "foo" and "bar" fields, e.g.

  type MyObject {
    foo: Int!
    bar: String!
  }

You could provide handlers for it like this:

>>> :m +System.Environment
>>> let fooHandler = pure 42
>>> let barHandler = System.Environment.getProgName
>>> let myObjectHandler = pure $ fooHandler :<> barHandler :<> ()

Constructors

a :<> b infixr 8 

data Result a Source #

Constructors

Result [ResolverError] a 
Instances
Functor Result Source # 
Instance details

Defined in GraphQL.Internal.Resolver

Methods

fmap :: (a -> b) -> Result a -> Result b #

(<$) :: a -> Result b -> Result a #

Applicative Result Source # 
Instance details

Defined in GraphQL.Internal.Resolver

Methods

pure :: a -> Result a #

(<*>) :: Result (a -> b) -> Result a -> Result b #

liftA2 :: (a -> b -> c) -> Result a -> Result b -> Result c #

(*>) :: Result a -> Result b -> Result b #

(<*) :: Result a -> Result b -> Result a #

Eq a => Eq (Result a) Source # 
Instance details

Defined in GraphQL.Internal.Resolver

Methods

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

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

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

Defined in GraphQL.Internal.Resolver

Methods

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

show :: Result a -> String #

showList :: [Result a] -> ShowS #

unionValue :: forall (object :: Type) (union :: Type) m (name :: Symbol) interfaces fields. (Monad m, Object name interfaces fields ~ object, KnownSymbol name) => TypeIndex m object union -> m (DynamicUnionValue union m) Source #

Translate a Handler into a DynamicUnionValue type required by Union handlers. This is dynamic, but nevertheless type-safe because we can only tag with types that are part of the union.

Use e.g. like "unionValue @Cat" if you have an object like this:

>>> type Cat = API.Object "Cat" '[] '[API.Field "name" Text]

and then use `unionValue @Cat (pure (pure Felix))`. See `examples/UnionExample.hs` for more code.

resolveOperation :: forall m fields typeName interfaces. OperationResolverConstraint m fields typeName interfaces => Handler m (Object typeName interfaces fields) -> SelectionSetByType Value -> m (Result Object) Source #

returns :: Applicative f => a -> f (HandlerResult a) Source #

returns is a convenience function for a Handler that is returning the expected value.

handlerError :: Applicative f => Text -> f (HandlerResult a) Source #

handlerError is a convenience function for a Handler that has encountered an error and is unable to return the expected value.