Safe Haskell | None |
---|---|
Language | Haskell2010 |
Output types and values, monad transformer stack used by the GraphQL
resolvers.
This module is intended to be imported qualified, to avoid name clashes
with In
.
Synopsis
- data Context = Context {}
- data Field m = Field (Maybe Text) (Type m) Arguments
- data InterfaceType m = InterfaceType Name (Maybe Text) [InterfaceType m] (HashMap Name (Field m))
- data ObjectType m = ObjectType Name (Maybe Text) [InterfaceType m] (HashMap Name (Resolver m))
- type Resolve m = ReaderT Context m Value
- type Subscribe m = ReaderT Context m (SourceEventStream m)
- data Resolver m
- = ValueResolver (Field m) (Resolve m)
- | EventStreamResolver (Field m) (Resolve m) (Subscribe m)
- type SourceEventStream m = ConduitT () Value m ()
- data Type m
- = NamedScalarType ScalarType
- | NamedEnumType EnumType
- | NamedObjectType (ObjectType m)
- | NamedInterfaceType (InterfaceType m)
- | NamedUnionType (UnionType m)
- | ListType (Type m)
- | NonNullScalarType ScalarType
- | NonNullEnumType EnumType
- | NonNullObjectType (ObjectType m)
- | NonNullInterfaceType (InterfaceType m)
- | NonNullUnionType (UnionType m)
- | NonNullListType (Type m)
- data UnionType m = UnionType Name (Maybe Text) [ObjectType m]
- argument :: Monad m => Name -> Resolve m
- isNonNullType :: forall m. Type m -> Bool
- pattern EnumBaseType :: forall m. EnumType -> Type m
- pattern InterfaceBaseType :: forall m. InterfaceType m -> Type m
- pattern ListBaseType :: forall m. Type m -> Type m
- pattern ObjectBaseType :: forall m. ObjectType m -> Type m
- pattern ScalarBaseType :: forall m. ScalarType -> Type m
- pattern UnionBaseType :: forall m. UnionType m -> Type m
Documentation
Resolution context holds resolver arguments and the root value.
Output object field definition.
data InterfaceType m Source #
Interface Type Definition.
When a field can return one of a heterogeneous set of types, a Interface type is used to describe what types are possible, and what fields are in common across all types.
InterfaceType Name (Maybe Text) [InterfaceType m] (HashMap Name (Field m)) |
Instances
Eq (InterfaceType a) Source # | |
Defined in Language.GraphQL.Type.Out (==) :: InterfaceType a -> InterfaceType a -> Bool # (/=) :: InterfaceType a -> InterfaceType a -> Bool # | |
Show (InterfaceType a) Source # | |
Defined in Language.GraphQL.Type.Out showsPrec :: Int -> InterfaceType a -> ShowS # show :: InterfaceType a -> String # showList :: [InterfaceType a] -> ShowS # |
data ObjectType m Source #
Object type definition.
Almost all of the GraphQL types you define will be object types. Object types have a name, but most importantly describe their fields.
ObjectType Name (Maybe Text) [InterfaceType m] (HashMap Name (Resolver m)) |
Instances
Eq (ObjectType a) Source # | |
Defined in Language.GraphQL.Type.Out (==) :: ObjectType a -> ObjectType a -> Bool # (/=) :: ObjectType a -> ObjectType a -> Bool # | |
Show (ObjectType a) Source # | |
Defined in Language.GraphQL.Type.Out showsPrec :: Int -> ObjectType a -> ShowS # show :: ObjectType a -> String # showList :: [ObjectType a] -> ShowS # |
type Resolve m = ReaderT Context m Value Source #
Monad transformer stack used by the resolvers for determining the resolved value of a field.
type Subscribe m = ReaderT Context m (SourceEventStream m) Source #
Monad transformer stack used by the resolvers for determining the resolved event stream of a subscription field.
Resolver
associates some function(s) with each Field
. ValueResolver
resolves a Field
into a Value
. EventStreamResolver
resolves
additionally a Field
into a SourceEventStream
if it is the field of a
root subscription type.
The resolvers aren't part of the Field
itself because not all fields
have resolvers (interface fields don't have an implementation).
ValueResolver (Field m) (Resolve m) | |
EventStreamResolver (Field m) (Resolve m) (Subscribe m) |
type SourceEventStream m = ConduitT () Value m () Source #
A source stream represents the sequence of events, each of which will trigger a GraphQL execution corresponding to that event.
These types may be used as output types as the result of fields.
GraphQL distinguishes between "wrapping" and "named" types. Each wrapping type can wrap other wrapping or named types. Wrapping types are lists and Non-Null types (named types are nullable by default).
Union Type Definition.
When a field can return one of a heterogeneous set of types, a Union type is used to describe what types are possible.
UnionType Name (Maybe Text) [ObjectType m] |
argument :: Monad m => Name -> Resolve m Source #
Retrieves an argument by its name. If the argument with this name couldn't
be found, returns Null
(i.e. the argument is assumed to
be optional then).
isNonNullType :: forall m. Type m -> Bool Source #
Checks whether the given output type is a non-null type.
pattern EnumBaseType :: forall m. EnumType -> Type m Source #
Matches either NamedEnumType
or NonNullEnumType
.
pattern InterfaceBaseType :: forall m. InterfaceType m -> Type m Source #
Matches either NamedInterfaceType
or NonNullInterfaceType
.
pattern ListBaseType :: forall m. Type m -> Type m Source #
Matches either ListType
or NonNullListType
.
pattern ObjectBaseType :: forall m. ObjectType m -> Type m Source #
Matches either NamedObjectType
or NonNullObjectType
.
pattern ScalarBaseType :: forall m. ScalarType -> Type m Source #
Matches either NamedScalarType
or NonNullScalarType
.
pattern UnionBaseType :: forall m. UnionType m -> Type m Source #
Matches either NamedUnionType
or NonNullUnionType
.