Safe Haskell | None |
---|---|
Language | Haskell2010 |
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.
- data Type
- data Builtin
- data TypeDefinition
- = TypeDefinitionObject ObjectTypeDefinition
- | TypeDefinitionInterface InterfaceTypeDefinition
- | TypeDefinitionUnion UnionTypeDefinition
- | TypeDefinitionScalar ScalarTypeDefinition
- | TypeDefinitionEnum EnumTypeDefinition
- | TypeDefinitionInputObject InputObjectTypeDefinition
- | TypeDefinitionTypeExtension TypeExtensionDefinition
- data Name
- data ArgumentDefinition = ArgumentDefinition Name (AnnotatedType InputType) (Maybe DefaultValue)
- newtype EnumValueDefinition = EnumValueDefinition Name
- data EnumTypeDefinition = EnumTypeDefinition Name [EnumValueDefinition]
- data FieldDefinition = FieldDefinition Name [ArgumentDefinition] (AnnotatedType Type)
- type Interfaces = [InterfaceTypeDefinition]
- data InterfaceTypeDefinition = InterfaceTypeDefinition Name (NonEmptyList FieldDefinition)
- newtype NonEmptyList a = NonEmptyList [a]
- data ObjectTypeDefinition = ObjectTypeDefinition Name Interfaces (NonEmptyList FieldDefinition)
- data UnionTypeDefinition = UnionTypeDefinition Name (NonEmptyList ObjectTypeDefinition)
- data InputType
- data InputTypeDefinition
- = InputTypeDefinitionObject InputObjectTypeDefinition
- | InputTypeDefinitionScalar ScalarTypeDefinition
- | InputTypeDefinitionEnum EnumTypeDefinition
- data InputObjectTypeDefinition = InputObjectTypeDefinition Name (NonEmptyList InputObjectFieldDefinition)
- data InputObjectFieldDefinition = InputObjectFieldDefinition Name (AnnotatedType InputType) (Maybe DefaultValue)
- data AnnotatedType t
- = TypeNamed t
- | TypeList (ListType t)
- | TypeNonNull (NonNullType t)
- newtype ListType t = ListType (AnnotatedType t)
- data NonNullType t
- = NonNullTypeNamed t
- | NonNullTypeList (ListType t)
- class DefinesTypes t where
- doesFragmentTypeApply :: ObjectTypeDefinition -> TypeDefinition -> Bool
- data Schema
- makeSchema :: ObjectTypeDefinition -> Schema
- lookupType :: Schema -> Name -> Maybe TypeDefinition
Documentation
Builtin types
Types that are built into GraphQL.
The GraphQL spec refers to these as "[scalars](https:/facebook.github.iographql/#sec-Scalars)".
Defining new types
data TypeDefinition Source #
A name in GraphQL.
data ArgumentDefinition Source #
ArgumentDefinition Name (AnnotatedType InputType) (Maybe DefaultValue) |
newtype EnumValueDefinition Source #
data EnumTypeDefinition Source #
data FieldDefinition Source #
type Interfaces = [InterfaceTypeDefinition] Source #
newtype NonEmptyList a Source #
NonEmptyList [a] |
Functor NonEmptyList Source # | |
Foldable NonEmptyList Source # | |
Eq a => Eq (NonEmptyList a) Source # | |
Ord a => Ord (NonEmptyList a) Source # | |
Show a => Show (NonEmptyList a) Source # | |
data ObjectTypeDefinition Source #
data UnionTypeDefinition Source #
Input types
data InputTypeDefinition Source #
data InputObjectFieldDefinition Source #
InputObjectFieldDefinition Name (AnnotatedType InputType) (Maybe DefaultValue) |
Using existing types
data AnnotatedType t Source #
TypeNamed t | |
TypeList (ListType t) | |
TypeNonNull (NonNullType t) |
Eq t => Eq (AnnotatedType t) Source # | |
Ord t => Ord (AnnotatedType t) Source # | |
Show t => Show (AnnotatedType t) Source # | |
HasName t => HasName (AnnotatedType t) Source # | |
data NonNullType t Source #
Eq t => Eq (NonNullType t) Source # | |
Ord t => Ord (NonNullType t) Source # | |
Show t => Show (NonNullType t) Source # | |
class DefinesTypes t where Source #
A thing that defines types. Excludes definitions of input types.
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
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.