graphql-api-0.3.0: GraphQL API

Safe HaskellNone
LanguageHaskell2010

GraphQL.Resolver

Synopsis

Documentation

data ResolverError Source #

Constructors

SchemaError NameError

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.

class HasResolver m a where Source #

Minimal complete definition

resolve

Associated Types

type Handler m a Source #

Instances

Applicative m => HasResolver * m Bool Source # 

Associated Types

type Handler m (Bool :: * -> *) (a :: m) :: * Source #

Applicative m => HasResolver * m Text Source # 

Associated Types

type Handler m (Text :: * -> *) (a :: m) :: * Source #

Applicative m => HasResolver * m Double Source # 

Associated Types

type Handler m (Double :: * -> *) (a :: m) :: * Source #

Applicative m => HasResolver * m Int32 Source # 

Associated Types

type Handler m (Int32 :: * -> *) (a :: m) :: * Source #

(HasResolver * m hg, Monad m) => HasResolver * m (Maybe hg) Source # 

Associated Types

type Handler m (Maybe hg :: * -> *) (a :: m) :: * Source #

(Monad m, Applicative m, HasResolver Type m hg) => HasResolver * m (List hg) Source # 

Associated Types

type Handler m (List hg :: * -> *) (a :: m) :: * Source #

(Monad m, KnownSymbol unionName, RunUnion [Type] m (Union unionName objects) objects) => HasResolver * m (Union unionName objects) Source # 

Associated Types

type Handler m (Union unionName objects :: * -> *) (a :: m) :: * Source #

Methods

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

(Applicative m, GraphQLEnum enum) => HasResolver * m (Enum ksN enum) Source # 

Associated Types

type Handler m (Enum ksN enum :: * -> *) (a :: m) :: * Source #

Methods

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

(RunFields m (RunFieldsType m fields), HasObjectDefinition * (Object typeName interfaces fields), Monad m) => HasResolver * m (Object typeName interfaces fields) Source # 

Associated Types

type Handler m (Object typeName interfaces fields :: * -> *) (a :: m) :: * Source #

Methods

resolve :: Handler m (Object typeName interfaces fields) a -> Maybe (SelectionSetByType Value) -> Object typeName interfaces fields (Result Value) 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 # 

Methods

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

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

Applicative Result Source # 

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 # 

Methods

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

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

Show a => Show (Result a) Source # 

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.