graphql-api-0.2.0: Sketch of GraphQL stuff

Safe HaskellNone
LanguageHaskell2010

GraphQL.Internal.Schema

Contents

Description

Fully realized GraphQL schema type system at the value level.

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

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

Defining new types

newtype NonEmptyList a Source #

Constructors

NonEmptyList [a] 

Instances

Functor NonEmptyList Source # 

Methods

fmap :: (a -> b) -> NonEmptyList a -> NonEmptyList b #

(<$) :: a -> NonEmptyList b -> NonEmptyList a #

Foldable NonEmptyList Source # 

Methods

fold :: Monoid m => NonEmptyList m -> m #

foldMap :: Monoid m => (a -> m) -> NonEmptyList a -> m #

foldr :: (a -> b -> b) -> b -> NonEmptyList a -> b #

foldr' :: (a -> b -> b) -> b -> NonEmptyList a -> b #

foldl :: (b -> a -> b) -> b -> NonEmptyList a -> b #

foldl' :: (b -> a -> b) -> b -> NonEmptyList a -> b #

foldr1 :: (a -> a -> a) -> NonEmptyList a -> a #

foldl1 :: (a -> a -> a) -> NonEmptyList a -> a #

toList :: NonEmptyList a -> [a] #

null :: NonEmptyList a -> Bool #

length :: NonEmptyList a -> Int #

elem :: Eq a => a -> NonEmptyList a -> Bool #

maximum :: Ord a => NonEmptyList a -> a #

minimum :: Ord a => NonEmptyList a -> a #

sum :: Num a => NonEmptyList a -> a #

product :: Num a => NonEmptyList a -> a #

Eq a => Eq (NonEmptyList a) Source # 
Ord a => Ord (NonEmptyList a) Source # 
Show a => Show (NonEmptyList a) Source # 

Input types

Using existing types

newtype ListType t Source #

Constructors

ListType (AnnotatedType t) 

Instances

Eq t => Eq (ListType t) Source # 

Methods

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

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

Ord t => Ord (ListType t) Source # 

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 # 

Methods

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

show :: ListType t -> String #

showList :: [ListType t] -> ShowS #

class DefinesTypes t where Source #

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

Minimal complete definition

getDefinedTypes

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.

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.

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.

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.

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

Find the type with the given name in the schema.