Safe Haskell | None |
---|---|
Language | Haskell2010 |
GraphQL.Internal.Schema
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
- data GType
- 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 GType)
- type Interfaces = [InterfaceTypeDefinition]
- data InterfaceTypeDefinition = InterfaceTypeDefinition Name (NonEmpty FieldDefinition)
- data ObjectTypeDefinition = ObjectTypeDefinition Name Interfaces (NonEmpty FieldDefinition)
- data UnionTypeDefinition = UnionTypeDefinition Name (NonEmpty ObjectTypeDefinition)
- newtype ScalarTypeDefinition = ScalarTypeDefinition Name
- data InputType
- data InputTypeDefinition
- data InputObjectTypeDefinition = InputObjectTypeDefinition Name (NonEmpty 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
- getDefinedTypes :: t -> Map Name TypeDefinition
- doesFragmentTypeApply :: ObjectTypeDefinition -> TypeDefinition -> Bool
- getInputTypeDefinition :: TypeDefinition -> Maybe InputTypeDefinition
- builtinFromName :: Name -> Maybe Builtin
- astAnnotationToSchemaAnnotation :: GType -> a -> AnnotatedType a
- data Schema
- makeSchema :: ObjectTypeDefinition -> Schema
- emptySchema :: Schema
- lookupType :: Schema -> Name -> Maybe TypeDefinition
Documentation
Constructors
DefinedType TypeDefinition | |
BuiltinType Builtin |
Builtin types
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
data TypeDefinition Source #
Constructors
Instances
A name in GraphQL.
data ArgumentDefinition Source #
Constructors
ArgumentDefinition Name (AnnotatedType InputType) (Maybe DefaultValue) |
Instances
newtype EnumValueDefinition Source #
Constructors
EnumValueDefinition Name |
Instances
data EnumTypeDefinition Source #
Constructors
EnumTypeDefinition Name [EnumValueDefinition] |
Instances
data FieldDefinition Source #
Constructors
FieldDefinition Name [ArgumentDefinition] (AnnotatedType GType) |
Instances
type Interfaces = [InterfaceTypeDefinition] Source #
data InterfaceTypeDefinition Source #
Constructors
InterfaceTypeDefinition Name (NonEmpty FieldDefinition) |
Instances
data ObjectTypeDefinition Source #
Constructors
ObjectTypeDefinition Name Interfaces (NonEmpty FieldDefinition) |
Instances
data UnionTypeDefinition Source #
Constructors
UnionTypeDefinition Name (NonEmpty ObjectTypeDefinition) |
Instances
newtype ScalarTypeDefinition Source #
Constructors
ScalarTypeDefinition Name |
Instances
Input types
Constructors
DefinedInputType InputTypeDefinition | |
BuiltinInputType Builtin |
Instances
Eq InputType Source # | |
Ord InputType Source # | |
Show InputType Source # | |
HasName InputType Source # | |
DefinesTypes InputType Source # | |
Defined in GraphQL.Internal.Schema Methods getDefinedTypes :: InputType -> Map Name TypeDefinition Source # |
data InputTypeDefinition Source #
Constructors
InputTypeDefinitionObject InputObjectTypeDefinition | |
InputTypeDefinitionScalar ScalarTypeDefinition | |
InputTypeDefinitionEnum EnumTypeDefinition |
Instances
data InputObjectTypeDefinition Source #
Constructors
InputObjectTypeDefinition Name (NonEmpty InputObjectFieldDefinition) |
Instances
data InputObjectFieldDefinition Source #
Constructors
InputObjectFieldDefinition Name (AnnotatedType InputType) (Maybe DefaultValue) |
Instances
Using existing types
data AnnotatedType t Source #
Constructors
TypeNamed t | |
TypeList (ListType t) | |
TypeNonNull (NonNullType t) |
Instances
Eq t => Eq (AnnotatedType t) Source # | |
Defined in GraphQL.Internal.Schema Methods (==) :: AnnotatedType t -> AnnotatedType t -> Bool # (/=) :: AnnotatedType t -> AnnotatedType t -> Bool # | |
Ord t => Ord (AnnotatedType t) Source # | |
Defined in GraphQL.Internal.Schema Methods compare :: AnnotatedType t -> AnnotatedType t -> Ordering # (<) :: AnnotatedType t -> AnnotatedType t -> Bool # (<=) :: AnnotatedType t -> AnnotatedType t -> Bool # (>) :: AnnotatedType t -> AnnotatedType t -> Bool # (>=) :: AnnotatedType t -> AnnotatedType t -> Bool # max :: AnnotatedType t -> AnnotatedType t -> AnnotatedType t # min :: AnnotatedType t -> AnnotatedType t -> AnnotatedType t # | |
Show t => Show (AnnotatedType t) Source # | |
Defined in GraphQL.Internal.Schema Methods showsPrec :: Int -> AnnotatedType t -> ShowS # show :: AnnotatedType t -> String # showList :: [AnnotatedType t] -> ShowS # | |
HasName t => HasName (AnnotatedType t) Source # | |
Defined in GraphQL.Internal.Schema Methods getName :: AnnotatedType t -> Name Source # |
Constructors
ListType (AnnotatedType t) |
Instances
Eq t => Eq (ListType t) Source # | |
Ord t => Ord (ListType t) Source # | |
Defined in GraphQL.Internal.Schema | |
Show t => Show (ListType t) Source # | |
data NonNullType t Source #
Constructors
NonNullTypeNamed t | |
NonNullTypeList (ListType t) |
Instances
Eq t => Eq (NonNullType t) Source # | |
Defined in GraphQL.Internal.Schema Methods (==) :: NonNullType t -> NonNullType t -> Bool # (/=) :: NonNullType t -> NonNullType t -> Bool # | |
Ord t => Ord (NonNullType t) Source # | |
Defined in GraphQL.Internal.Schema Methods compare :: NonNullType t -> NonNullType t -> Ordering # (<) :: NonNullType t -> NonNullType t -> Bool # (<=) :: NonNullType t -> NonNullType t -> Bool # (>) :: NonNullType t -> NonNullType t -> Bool # (>=) :: NonNullType t -> NonNullType t -> Bool # max :: NonNullType t -> NonNullType t -> NonNullType t # min :: NonNullType t -> NonNullType t -> NonNullType t # | |
Show t => Show (NonNullType t) Source # | |
Defined in GraphQL.Internal.Schema Methods showsPrec :: Int -> NonNullType t -> ShowS # show :: NonNullType t -> String # showList :: [NonNullType t] -> ShowS # |
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
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.
getInputTypeDefinition :: TypeDefinition -> Maybe InputTypeDefinition Source #
Convert the given TypeDefinition
to an InputTypeDefinition
if it's a valid InputTypeDefinition
(because InputTypeDefinition
is a subset of TypeDefinition
)
see http://facebook.github.io/graphql/June2018/#sec-Input-and-Output-Types
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
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.
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.