Safe Haskell | None |
---|---|
Language | Haskell2010 |
Reexports non-conflicting type system and schema definitions.
Synopsis
- data InputField = InputField (Maybe Text) Type (Maybe Value)
- data InputObjectType = InputObjectType Name (Maybe Text) (HashMap Name InputField)
- 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
- data Resolver m
- = ValueResolver (Field m) (Resolve m)
- | EventStreamResolver (Field m) (Resolve m) (Subscribe m)
- type SourceEventStream m = ConduitT () Value m ()
- type Subscribe m = ReaderT Context m (SourceEventStream m)
- data UnionType m = UnionType Name (Maybe Text) [ObjectType m]
- argument :: Monad m => Name -> Resolve m
- newtype Arguments = Arguments (HashMap Name Value)
- data Directive = Directive Name Arguments
- data EnumType = EnumType Name (Maybe Text) (HashMap Name EnumValue)
- newtype EnumValue = EnumValue (Maybe Text)
- data ScalarType = ScalarType Name (Maybe Text)
- type Subs = HashMap Name Value
- data Value
- boolean :: ScalarType
- float :: ScalarType
- id :: ScalarType
- int :: ScalarType
- selection :: [Directive] -> Maybe [Directive]
- string :: ScalarType
- data Schema m
- schema :: forall m. ObjectType m -> Maybe (ObjectType m) -> Maybe (ObjectType m) -> Directives -> Schema m
- schemaWithTypes :: forall m. Maybe Text -> ObjectType m -> Maybe (ObjectType m) -> Maybe (ObjectType m) -> [Type m] -> Directives -> Schema m
Documentation
data InputField Source #
Single field of an InputObjectType
.
data InputObjectType Source #
Input object type definition.
An input object defines a structured collection of fields which may be supplied to a field argument.
Instances
Eq InputObjectType Source # | |
Defined in Language.GraphQL.Type.In (==) :: InputObjectType -> InputObjectType -> Bool # (/=) :: InputObjectType -> InputObjectType -> Bool # | |
Show InputObjectType Source # | |
Defined in Language.GraphQL.Type.In showsPrec :: Int -> InputObjectType -> ShowS # show :: InputObjectType -> String # showList :: [InputObjectType] -> ShowS # |
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.
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.
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.
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).
Argument list.
Enum type definition.
Some leaf values of requests and input values are Enums. GraphQL serializes Enum values as strings, however internally Enums can be represented by any kind of type, often integers.
data ScalarType Source #
Scalar type definition.
The leaf values of any request and input values to arguments are Scalars (or Enums) .
Instances
Eq ScalarType Source # | |
Defined in Language.GraphQL.Type.Definition (==) :: ScalarType -> ScalarType -> Bool # (/=) :: ScalarType -> ScalarType -> Bool # | |
Show ScalarType Source # | |
Defined in Language.GraphQL.Type.Definition showsPrec :: Int -> ScalarType -> ShowS # show :: ScalarType -> String # showList :: [ScalarType] -> ShowS # |
type Subs = HashMap Name Value Source #
Contains variables for the query. The key of the map is a variable name, and the value is the variable value.
Represents accordingly typed GraphQL values.
Int Int32 | |
Float Double | GraphQL Float is double precision. |
String Text | |
Boolean Bool | |
Null | |
Enum Name | |
List [Value] | Arbitrary nested list. |
Object (HashMap Name Value) |
boolean :: ScalarType Source #
The Boolean
scalar type represents true
or false
.
float :: ScalarType Source #
The Float
scalar type represents signed double-precision fractional
values as specified by
IEEE 754.
id :: ScalarType Source #
The ID
scalar type represents a unique identifier, often used to refetch
an object or as key for a cache. The ID type appears in a JSON response as a
String; however, it is not intended to be human-readable. When expected as an
input type, any string (such as "4"
) or integer (such as 4
) input value
will be accepted as an ID.
int :: ScalarType Source #
The Int
scalar type represents non-fractional signed whole numeric
values. Int can represent values between \(-2^{31}\) and \(2^{31 - 1}\).
selection :: [Directive] -> Maybe [Directive] Source #
Takes a list of directives, handles supported directives and excludes them
from the result. If the selection should be skipped, returns Nothing
.
string :: ScalarType Source #
The String
scalar type represents textual data, represented as UTF-8
character sequences. The String type is most often used by GraphQL to
represent free-form human-readable text.
A Schema is created by supplying the root types of each type of operation, query and mutation (optional). A schema definition is then supplied to the validator and executor.
:: forall m. ObjectType m | Query type. |
-> Maybe (ObjectType m) | Mutation type. |
-> Maybe (ObjectType m) | Subscription type. |
-> Directives | Directive definitions. |
-> Schema m | Schema. |
Schema constructor.
Note: When the schema is constructed, by default only the types that
are reachable by traversing the root types are included, other types must
be explicitly referenced using schemaWithTypes
instead.
:: forall m. Maybe Text | Schema description |
-> ObjectType m | Query type. |
-> Maybe (ObjectType m) | Mutation type. |
-> Maybe (ObjectType m) | Subscription type. |
-> [Type m] | Additional types. |
-> Directives | Directive definitions. |
-> Schema m | Schema. |
Constructs a complete schema, including user-defined types not referenced in the schema directly (for example interface implementations).