graphql-1.3.0.0: Haskell GraphQL implementation
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.GraphQL.Type

Description

Reexports non-conflicting type system and schema definitions.

Synopsis

Documentation

data InputField Source #

Single field of an InputObjectType.

Constructors

InputField (Maybe Text) Type (Maybe Value) 

data InputObjectType Source #

Input object type definition.

An input object defines a structured collection of fields which may be supplied to a field argument.

data Context Source #

Resolution context holds resolver arguments and the root value.

Constructors

Context 

data Field m Source #

Output object field definition.

Constructors

Field 

Fields

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.

Instances

Instances details
Show (InterfaceType a) Source # 
Instance details

Defined in Language.GraphQL.Type.Out

Eq (InterfaceType a) Source # 
Instance details

Defined in Language.GraphQL.Type.Out

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.

Instances

Instances details
Show (ObjectType a) Source # 
Instance details

Defined in Language.GraphQL.Type.Out

Eq (ObjectType a) Source # 
Instance details

Defined in Language.GraphQL.Type.Out

Methods

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

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

type Resolve m = ReaderT Context m Value Source #

Monad transformer stack used by the resolvers for determining the resolved value of a field.

data Resolver m Source #

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).

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.

data UnionType m Source #

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.

Constructors

UnionType Name (Maybe Text) [ObjectType m] 

Instances

Instances details
Show (UnionType a) Source # 
Instance details

Defined in Language.GraphQL.Type.Out

Eq (UnionType a) Source # 
Instance details

Defined in Language.GraphQL.Type.Out

Methods

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

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

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).

data Directive Source #

Directive.

Constructors

Directive Name Arguments 

Instances

Instances details
Show Directive Source # 
Instance details

Defined in Language.GraphQL.Type.Definition

Eq Directive Source # 
Instance details

Defined in Language.GraphQL.Type.Definition

data EnumType Source #

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.

Instances

Instances details
Show EnumType Source # 
Instance details

Defined in Language.GraphQL.Type.Definition

Eq EnumType Source # 
Instance details

Defined in Language.GraphQL.Type.Definition

newtype EnumValue Source #

Enum value is a single member of an EnumType.

Constructors

EnumValue (Maybe Text) 

data ScalarType Source #

Scalar type definition.

The leaf values of any request and input values to arguments are Scalars (or Enums) .

Constructors

ScalarType Name (Maybe Text) 

Instances

Instances details
Show ScalarType Source # 
Instance details

Defined in Language.GraphQL.Type.Definition

Eq ScalarType Source # 
Instance details

Defined in Language.GraphQL.Type.Definition

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.

data Value Source #

Represents accordingly typed GraphQL values.

Constructors

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) 

Instances

Instances details
IsString Value Source # 
Instance details

Defined in Language.GraphQL.Type.Definition

Methods

fromString :: String -> Value #

Show Value Source # 
Instance details

Defined in Language.GraphQL.Type.Definition

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Eq Value Source # 
Instance details

Defined in Language.GraphQL.Type.Definition

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Serialize Value Source # 
Instance details

Defined in Language.GraphQL.Execute.Coerce

Methods

serialize :: forall (m :: Type -> Type). Type m -> Output Value -> Maybe Value Source #

null :: Value Source #

VariableValue Value Source # 
Instance details

Defined in Language.GraphQL.Execute.Coerce

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.

data Schema m Source #

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.

schema Source #

Arguments

:: 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.

schemaWithTypes Source #

Arguments

:: 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).