graphql-api-0.3.0: GraphQL API

Safe HaskellNone
LanguageHaskell2010

GraphQL.API

Description

Type-level definitions for a GraphQL schema.

Synopsis

Documentation

data Object (name :: Symbol) (interfaces :: [Type]) (fields :: [Type]) Source #

Instances

(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 #

(KnownSymbol ks, HasInterfaceDefinitions [Type] is, HasFieldDefinitions [Type] ts) => HasAnnotatedType * (Object ks is ts) Source # 
(KnownSymbol ks, HasInterfaceDefinitions [Type] is, HasFieldDefinitions [Type] fields) => HasObjectDefinition * (Object ks is fields) Source # 
type Handler * m (Object typeName interfaces fields) Source # 
type Handler * m (Object typeName interfaces fields)

data Field (name :: Symbol) (fieldType :: Type) Source #

data Argument (name :: Symbol) (argType :: Type) Source #

data Union (name :: Symbol) (types :: [Type]) Source #

Instances

(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 #

(KnownSymbol ks, HasUnionTypeObjectTypeDefinitions [Type] as) => HasAnnotatedType * (Union ks as) Source # 
type Handler * m (Union unionName objects) Source # 
type Handler * m (Union unionName objects)

data Enum (name :: Symbol) (values :: Type) Source #

Instances

(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 #

(KnownSymbol ks, GraphQLEnum enum) => HasAnnotatedType * (Enum ks enum) Source # 
(KnownSymbol ks, GraphQLEnum enum) => HasAnnotatedInputType (Enum ks enum) Source # 
type Handler * m (Enum ksN enum) Source # 
type Handler * m (Enum ksN enum) = m enum

class GraphQLEnum a where Source #

For each enum type we need 1) a list of all possible values 2) a way to serialise and 3) deserialise.

TODO: Update this comment to explain what a GraphQLEnum is, why you might want an instance, and any laws that apply to method relations.

Methods

enumValues :: [Either NameError Name] Source #

enumValues :: (Generic a, GenericEnumValues (Rep a)) => [Either NameError Name] Source #

enumFromValue :: Name -> Either Text a Source #

enumFromValue :: (Generic a, GenericEnumValues (Rep a)) => Name -> Either Text a Source #

enumToValue :: a -> Name Source #

enumToValue :: (Generic a, GenericEnumValues (Rep a)) => a -> Name Source #

data Interface (name :: Symbol) (fields :: [Type]) Source #

data a :> b infixr 8 Source #

Argument operator. Can only be used with Field.

Say we have a Company object that has a field that shows whether someone is an employee, e.g.

  type Company {
    hasEmployee(employeeName: String!): String!
  }

Then we might represent that as:

>>> type Company = Object "Company" '[] '[Argument "employeeName" Text :> Field "hasEmployee" Bool]

For multiple arguments, simply chain them together with :>, ending finally with Field. e.g.

  Argument "foo" String :> Argument "bar" Int :> Field "qux" Int

Constructors

a :> b infixr 8 

class Defaultable a where Source #

Specify a default value for a type in a GraphQL schema.

GraphQL schema can have default values in certain places. For example, arguments to fields can have default values. Because we cannot lift arbitrary values to the type level, we need some way of getting at those values. This typeclass provides the means.

To specify a default, implement this typeclass.

The default implementation is to say that there *is* no default for this type.

Methods

defaultFor :: Name -> Maybe a Source #

defaultFor returns the value to be used when no value has been given.

class HasAnnotatedType a where Source #

Minimal complete definition

getAnnotatedType

Instances

HasAnnotatedType * Bool Source # 
HasAnnotatedType * Double Source # 
HasAnnotatedType * Float Source # 
HasAnnotatedType * Int Source # 
HasAnnotatedType * Int32 Source # 
TypeError Constraint (Text "Cannot encode Integer because it has arbitrary size but the JSON encoding is a number") => HasAnnotatedType * Integer Source # 
HasAnnotatedType * Text Source # 
HasAnnotatedType * a => HasAnnotatedType * (Maybe a) Source # 
HasAnnotatedType Type t => HasAnnotatedType * (List t) Source # 
(KnownSymbol ks, HasUnionTypeObjectTypeDefinitions [Type] as) => HasAnnotatedType * (Union ks as) Source # 
(KnownSymbol ks, GraphQLEnum enum) => HasAnnotatedType * (Enum ks enum) Source # 
(KnownSymbol ks, HasInterfaceDefinitions [Type] is, HasFieldDefinitions [Type] ts) => HasAnnotatedType * (Object ks is ts) Source # 

class HasObjectDefinition a where Source #

Minimal complete definition

getDefinition

Instances

(KnownSymbol ks, HasInterfaceDefinitions [Type] is, HasFieldDefinitions [Type] fields) => HasObjectDefinition * (Object ks is fields) Source # 

Exported for testing. Perhaps should be a different module.