graphql-api-0.4.0: GraphQL API

Safe HaskellNone
LanguageHaskell2010

GraphQL.Internal.Schema

Contents

Description

Differs from Data.GraphQL.AST in the graphql package in that there are no type references. Instead, everything is inlined.

Equivalent representation of GraphQL values is in GraphQL.Value.

Synopsis

Documentation

data GType Source #

Instances
Eq GType Source # 
Instance details

Defined in GraphQL.Internal.Schema

Methods

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

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

Ord GType Source # 
Instance details

Defined in GraphQL.Internal.Schema

Methods

compare :: GType -> GType -> Ordering #

(<) :: GType -> GType -> Bool #

(<=) :: GType -> GType -> Bool #

(>) :: GType -> GType -> Bool #

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

max :: GType -> GType -> GType #

min :: GType -> GType -> GType #

Show GType Source # 
Instance details

Defined in GraphQL.Internal.Schema

Methods

showsPrec :: Int -> GType -> ShowS #

show :: GType -> String #

showList :: [GType] -> ShowS #

HasName GType Source # 
Instance details

Defined in GraphQL.Internal.Schema

Methods

getName :: GType -> Name Source #

DefinesTypes GType Source # 
Instance details

Defined in GraphQL.Internal.Schema

Builtin types

data Builtin Source #

Types that are built into GraphQL.

The GraphQL spec refers to these as "[scalars](https:/facebook.github.iographql/#sec-Scalars)".

Constructors

GInt

A signed 32‐bit numeric non‐fractional value

GBool

True or false

GString

Textual data represented as UTF-8 character sequences

GFloat

Signed double‐precision fractional values as specified by IEEE 754

GID

A unique identifier, often used to refetch an object or as the key for a cache

Instances
Eq Builtin Source # 
Instance details

Defined in GraphQL.Internal.Schema

Methods

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

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

Ord Builtin Source # 
Instance details

Defined in GraphQL.Internal.Schema

Show Builtin Source # 
Instance details

Defined in GraphQL.Internal.Schema

HasName Builtin Source # 
Instance details

Defined in GraphQL.Internal.Schema

Methods

getName :: Builtin -> Name Source #

Defining new types

data TypeDefinition Source #

data Name Source #

Instances
Eq Name Source # 
Instance details

Defined in GraphQL.Internal.Name

Methods

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

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

Ord Name Source # 
Instance details

Defined in GraphQL.Internal.Name

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

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

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name Source # 
Instance details

Defined in GraphQL.Internal.Name

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

IsString Name Source # 
Instance details

Defined in GraphQL.Internal.Name

Methods

fromString :: String -> Name #

Arbitrary Name Source # 
Instance details

Defined in GraphQL.Internal.Name

Methods

arbitrary :: Gen Name #

shrink :: Name -> [Name] #

ToJSON Name Source # 
Instance details

Defined in GraphQL.Internal.Name

data InterfaceTypeDefinition Source #

Input types

data InputTypeDefinition Source #

Using existing types

newtype ListType t Source #

Constructors

ListType (AnnotatedType t) 
Instances
Eq t => Eq (ListType t) Source # 
Instance details

Defined in GraphQL.Internal.Schema

Methods

(==) :: ListType t -> ListType t -> Bool #

(/=) :: ListType t -> ListType t -> Bool #

Ord t => Ord (ListType t) Source # 
Instance details

Defined in GraphQL.Internal.Schema

Methods

compare :: ListType t -> ListType t -> Ordering #

(<) :: ListType t -> ListType t -> Bool #

(<=) :: ListType t -> ListType t -> Bool #

(>) :: ListType t -> ListType t -> Bool #

(>=) :: ListType t -> ListType t -> Bool #

max :: ListType t -> ListType t -> ListType t #

min :: ListType t -> ListType t -> ListType t #

Show t => Show (ListType t) Source # 
Instance details

Defined in GraphQL.Internal.Schema

Methods

showsPrec :: Int -> ListType t -> ShowS #

show :: ListType t -> String #

showList :: [ListType t] -> ShowS #

data NonNullType t Source #

Instances
Eq t => Eq (NonNullType t) Source # 
Instance details

Defined in GraphQL.Internal.Schema

Ord t => Ord (NonNullType t) Source # 
Instance details

Defined in GraphQL.Internal.Schema

Show t => Show (NonNullType t) Source # 
Instance details

Defined in GraphQL.Internal.Schema

class DefinesTypes t where Source #

A thing that defines types. Excludes definitions of input types.

Methods

getDefinedTypes :: t -> Map Name TypeDefinition Source #

Get the types defined by t

TODO: This ignores whether a value can define multiple types with the same name, and further admits the possibility that the name embedded in the type definition does not match the name in the returned dictionary. jml would like to have a schema validation phase that eliminates one or both of these possibilities.

Also pretty much works because we've inlined all our type definitions.

Instances
DefinesTypes InputTypeDefinition Source # 
Instance details

Defined in GraphQL.Internal.Schema

DefinesTypes InputType Source # 
Instance details

Defined in GraphQL.Internal.Schema

DefinesTypes EnumTypeDefinition Source # 
Instance details

Defined in GraphQL.Internal.Schema

DefinesTypes ScalarTypeDefinition Source # 
Instance details

Defined in GraphQL.Internal.Schema

DefinesTypes UnionTypeDefinition Source # 
Instance details

Defined in GraphQL.Internal.Schema

DefinesTypes InterfaceTypeDefinition Source # 
Instance details

Defined in GraphQL.Internal.Schema

DefinesTypes ArgumentDefinition Source # 
Instance details

Defined in GraphQL.Internal.Schema

DefinesTypes FieldDefinition Source # 
Instance details

Defined in GraphQL.Internal.Schema

DefinesTypes ObjectTypeDefinition Source # 
Instance details

Defined in GraphQL.Internal.Schema

DefinesTypes TypeDefinition Source # 
Instance details

Defined in GraphQL.Internal.Schema

DefinesTypes GType Source # 
Instance details

Defined in GraphQL.Internal.Schema

doesFragmentTypeApply :: ObjectTypeDefinition -> TypeDefinition -> Bool Source #

Does the given object type match the given type condition.

See https://facebook.github.io/graphql/#sec-Field-Collection

DoesFragmentTypeApply(objectType, fragmentType)
  If fragmentType is an Object Type:
    if objectType and fragmentType are the same type, return true, otherwise return false.
  If fragmentType is an Interface Type:
    if objectType is an implementation of fragmentType, return true otherwise return false.
  If fragmentType is a Union:
    if objectType is a possible type of fragmentType, return true otherwise return false.

builtinFromName :: Name -> Maybe Builtin Source #

Create a Builtin type from a Name

Mostly used for the AST validation theobat: There's probably a better way to do it but can't find it right now

astAnnotationToSchemaAnnotation :: GType -> a -> AnnotatedType a Source #

Simple translation between AST annotation types and Schema annotation types

AST type annotations do not need any validation. GraphQL annotations are semantic decorations around type names to indicate type composition (list/non null).

The schema

data Schema Source #

An entire GraphQL schema.

This is very much a work in progress. Currently, the only thing we provide is a dictionary mapping type names to their definitions.

Instances
Eq Schema Source # 
Instance details

Defined in GraphQL.Internal.Schema

Methods

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

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

Ord Schema Source # 
Instance details

Defined in GraphQL.Internal.Schema

Show Schema Source # 
Instance details

Defined in GraphQL.Internal.Schema

makeSchema :: ObjectTypeDefinition -> Schema Source #

Create a schema from the root object.

This is technically an insufficient API, since not all types in a schema need to be reachable from a single root object. However, it's a start.

emptySchema :: Schema Source #

Create an empty schema for testing purpose.

lookupType :: Schema -> Name -> Maybe TypeDefinition Source #

Find the type with the given name in the schema.