Safe Haskell | None |
---|---|
Language | Haskell2010 |
This corresponds roughly to the Validation section of the specification, except where noted.
One core difference is that this module doesn't attempt to do any type-level validation, as we attempt to defer all of that to the Haskell type checker.
Deliberately not going to do:
- field selections on compound types https://facebook.github.io/graphql/#sec-Field-Selections-on-Objects-Interfaces-and-Unions-Types
- leaf field selections https://facebook.github.io/graphql/#sec-Leaf-Field-Selections
- argument names https://facebook.github.io/graphql/#sec-Argument-Names
- argument value type correctness https://facebook.github.io/graphql/#sec-Argument-Values-Type-Correctness
- fragment spread type existence https://facebook.github.io/graphql/#sec-Fragment-Spread-Type-Existence
- fragments on compound types https://facebook.github.io/graphql/#sec-Fragments-On-Composite-Types
- fragment spread is possible https://facebook.github.io/graphql/#sec-Fragment-spread-is-possible
- directives are defined https://facebook.github.io/graphql/#sec-Directives-Are-Defined
- directives are in valid locations https://facebook.github.io/graphql/#sec-Directives-Are-In-Valid-Locations
- variable default values are correctly typed https://facebook.github.io/graphql/#sec-Variable-Default-Values-Are-Correctly-Typed
- variables are input types https://facebook.github.io/graphql/#sec-Variables-Are-Input-Types
- all variable usages are allowed https://facebook.github.io/graphql/#sec-All-Variable-Usages-are-Allowed
Because all of the above rely on type checking.
Synopsis
- data ValidationError
- = DuplicateOperation (Maybe Name)
- | MixedAnonymousOperations Int [Maybe Name]
- | DuplicateArgument Name
- | DuplicateFragmentDefinition Name
- | NoSuchFragment Name
- | DuplicateDirective Name
- | DuplicateVariableDefinition Variable
- | CircularFragmentSpread Name
- | UnusedFragments (Set (Maybe Name))
- | UnusedVariables (Set Variable)
- | UndefinedVariable Variable
- | InvalidValue Value
- | InvalidDefaultValue Value
- | MismatchedNames Name Name
- | MismatchedArguments Name
- | IncompatibleFields Name
- | TypeConditionNotFound Name
- | VariableTypeNotFound Variable Name
- | VariableTypeIsNotInputType Variable Name
- type ValidationErrors = NonEmpty ValidationError
- data QueryDocument value
- = LoneAnonymousOperation (Operation value)
- | MultipleOperations (Operations value)
- validate :: Schema -> QueryDocument -> Either (NonEmpty ValidationError) (QueryDocument VariableValue)
- getErrors :: Schema -> QueryDocument -> [ValidationError]
- data Operation value
- getSelectionSet :: Operation value -> SelectionSetByType value
- data VariableDefinition = VariableDefinition {}
- type VariableValue = Value' (Either VariableDefinition ConstScalar)
- data Variable
- data GType
- data SelectionSetByType value
- newtype SelectionSet value = SelectionSet (OrderedMap ResponseKey (Field value))
- getSelectionSetForType :: Eq value => ObjectTypeDefinition -> SelectionSetByType value -> Either ValidationErrors (SelectionSet value)
- data Field value
- lookupArgument :: Field value -> Name -> Maybe value
- getSubSelectionSet :: Field value -> Maybe (SelectionSetByType value)
- type ResponseKey = Name
- getResponseKey :: Field' spread value -> ResponseKey
- findDuplicates :: Ord a => [a] -> [a]
- formatErrors :: [ValidationError] -> [Text]
Documentation
data ValidationError Source #
Errors arising from validating a document.
DuplicateOperation (Maybe Name) |
https://facebook.github.io/graphql/#sec-Operation-Name-Uniqueness |
MixedAnonymousOperations Int [Maybe Name] |
https://facebook.github.io/graphql/#sec-Lone-Anonymous-Operation |
DuplicateArgument Name |
|
DuplicateFragmentDefinition Name |
|
NoSuchFragment Name |
|
DuplicateDirective Name |
https://facebook.github.io/graphql/#sec-Directives-Are-Unique-Per-Location |
DuplicateVariableDefinition Variable | There were multiple variables defined with the same name. |
CircularFragmentSpread Name |
|
UnusedFragments (Set (Maybe Name)) |
|
UnusedVariables (Set Variable) | Variables were defined without being used. https://facebook.github.io/graphql/#sec-All-Variables-Used |
UndefinedVariable Variable | A variable was used without being defined. https://facebook.github.io/graphql/#sec-All-Variable-Uses-Defined |
InvalidValue Value | Value in AST wasn't valid. |
InvalidDefaultValue Value | Default value in AST contained variables. |
MismatchedNames Name Name | Two different names given for the same response key. |
MismatchedArguments Name | Two different sets of arguments given for the same response key. |
IncompatibleFields Name | Two fields had the same response key, one was a leaf, the other was not. |
TypeConditionNotFound Name | There's a type condition that's not present in the schema. |
VariableTypeNotFound Variable Name | There's a variable type that's not present in the schema. |
VariableTypeIsNotInputType Variable Name | A variable was defined with a non input type. http://facebook.github.io/graphql/June2018/#sec-Variables-Are-Input-Types |
Instances
Eq ValidationError Source # | |
Defined in GraphQL.Internal.Validation (==) :: ValidationError -> ValidationError -> Bool # (/=) :: ValidationError -> ValidationError -> Bool # | |
Show ValidationError Source # | |
Defined in GraphQL.Internal.Validation showsPrec :: Int -> ValidationError -> ShowS # show :: ValidationError -> String # showList :: [ValidationError] -> ShowS # | |
GraphQLError ValidationError Source # | |
Defined in GraphQL.Internal.Validation formatError :: ValidationError -> Text Source # toError :: ValidationError -> Error Source # |
data QueryDocument value Source #
A valid query document.
Construct this using validate
on an QueryDocument
.
LoneAnonymousOperation (Operation value) | The query document contains a single anonymous operation. |
MultipleOperations (Operations value) | The query document contains multiple uniquely-named operations. |
Instances
Eq value => Eq (QueryDocument value) Source # | |
Defined in GraphQL.Internal.Validation (==) :: QueryDocument value -> QueryDocument value -> Bool # (/=) :: QueryDocument value -> QueryDocument value -> Bool # | |
Show value => Show (QueryDocument value) Source # | |
Defined in GraphQL.Internal.Validation showsPrec :: Int -> QueryDocument value -> ShowS # show :: QueryDocument value -> String # showList :: [QueryDocument value] -> ShowS # |
validate :: Schema -> QueryDocument -> Either (NonEmpty ValidationError) (QueryDocument VariableValue) Source #
Turn a parsed document into a known valid one.
The document is known to be syntactically valid, as we've got its AST. Here, we confirm that it's semantically valid (modulo types).
getErrors :: Schema -> QueryDocument -> [ValidationError] Source #
Identify all of the validation errors in doc
.
An empty list means no errors.
Operating on validated documents
Instances
Functor Operation Source # | |
Foldable Operation Source # | |
Defined in GraphQL.Internal.Validation fold :: Monoid m => Operation m -> m # foldMap :: Monoid m => (a -> m) -> Operation a -> m # foldr :: (a -> b -> b) -> b -> Operation a -> b # foldr' :: (a -> b -> b) -> b -> Operation a -> b # foldl :: (b -> a -> b) -> b -> Operation a -> b # foldl' :: (b -> a -> b) -> b -> Operation a -> b # foldr1 :: (a -> a -> a) -> Operation a -> a # foldl1 :: (a -> a -> a) -> Operation a -> a # toList :: Operation a -> [a] # length :: Operation a -> Int # elem :: Eq a => a -> Operation a -> Bool # maximum :: Ord a => Operation a -> a # minimum :: Ord a => Operation a -> a # | |
Traversable Operation Source # | |
Defined in GraphQL.Internal.Validation | |
Eq value => Eq (Operation value) Source # | |
Show value => Show (Operation value) Source # | |
getSelectionSet :: Operation value -> SelectionSetByType value Source #
Get the selection set for an operation.
Executing validated documents
data VariableDefinition Source #
Defines a variable within the context of an operation.
See https://facebook.github.io/graphql/#sec-Language.Variables
VariableDefinition | |
|
Instances
Eq VariableDefinition Source # | |
Defined in GraphQL.Internal.Validation (==) :: VariableDefinition -> VariableDefinition -> Bool # (/=) :: VariableDefinition -> VariableDefinition -> Bool # | |
Ord VariableDefinition Source # | |
Defined in GraphQL.Internal.Validation compare :: VariableDefinition -> VariableDefinition -> Ordering # (<) :: VariableDefinition -> VariableDefinition -> Bool # (<=) :: VariableDefinition -> VariableDefinition -> Bool # (>) :: VariableDefinition -> VariableDefinition -> Bool # (>=) :: VariableDefinition -> VariableDefinition -> Bool # max :: VariableDefinition -> VariableDefinition -> VariableDefinition # min :: VariableDefinition -> VariableDefinition -> VariableDefinition # | |
Show VariableDefinition Source # | |
Defined in GraphQL.Internal.Validation showsPrec :: Int -> VariableDefinition -> ShowS # show :: VariableDefinition -> String # showList :: [VariableDefinition] -> ShowS # |
type VariableValue = Value' (Either VariableDefinition ConstScalar) Source #
A GraphQL value which might contain some defined variables.
Resolving queries
data SelectionSetByType value Source #
Instances
newtype SelectionSet value Source #
A selection set, almost fully validated.
Sub-selection sets might not be validated.
SelectionSet (OrderedMap ResponseKey (Field value)) |
Instances
Eq value => Eq (SelectionSet value) Source # | |
Defined in GraphQL.Internal.Validation (==) :: SelectionSet value -> SelectionSet value -> Bool # (/=) :: SelectionSet value -> SelectionSet value -> Bool # | |
Ord value => Ord (SelectionSet value) Source # | |
Defined in GraphQL.Internal.Validation compare :: SelectionSet value -> SelectionSet value -> Ordering # (<) :: SelectionSet value -> SelectionSet value -> Bool # (<=) :: SelectionSet value -> SelectionSet value -> Bool # (>) :: SelectionSet value -> SelectionSet value -> Bool # (>=) :: SelectionSet value -> SelectionSet value -> Bool # max :: SelectionSet value -> SelectionSet value -> SelectionSet value # min :: SelectionSet value -> SelectionSet value -> SelectionSet value # | |
Show value => Show (SelectionSet value) Source # | |
Defined in GraphQL.Internal.Validation showsPrec :: Int -> SelectionSet value -> ShowS # show :: SelectionSet value -> String # showList :: [SelectionSet value] -> ShowS # |
getSelectionSetForType Source #
:: Eq value | |
=> ObjectTypeDefinition | The type of the object that the selection set is for |
-> SelectionSetByType value | A selection set with type conditions, obtained from the validation process |
-> Either ValidationErrors (SelectionSet value) | A flattened selection set without type conditions. It's possible that some of the fields in various types are not mergeable, in which case, we'll return a validation error. |
Once we know the GraphQL type of the object that a selection set (i.e. a
SelectionSetByType
) is for, we can eliminate all the irrelevant types and
present a single, flattened map of ResponseKey
to Field
.
A field ready to be resolved.
Instances
Functor Field Source # | |
Foldable Field Source # | |
Defined in GraphQL.Internal.Validation fold :: Monoid m => Field m -> m # foldMap :: Monoid m => (a -> m) -> Field a -> m # foldr :: (a -> b -> b) -> b -> Field a -> b # foldr' :: (a -> b -> b) -> b -> Field a -> b # foldl :: (b -> a -> b) -> b -> Field a -> b # foldl' :: (b -> a -> b) -> b -> Field a -> b # foldr1 :: (a -> a -> a) -> Field a -> a # foldl1 :: (a -> a -> a) -> Field a -> a # elem :: Eq a => a -> Field a -> Bool # maximum :: Ord a => Field a -> a # minimum :: Ord a => Field a -> a # | |
Traversable Field Source # | |
Eq value => Eq (Field value) Source # | |
Ord value => Ord (Field value) Source # | |
Defined in GraphQL.Internal.Validation | |
Show value => Show (Field value) Source # | |
HasName (Field value) Source # | |
lookupArgument :: Field value -> Name -> Maybe value Source #
Get the value of an argument in a field.
getSubSelectionSet :: Field value -> Maybe (SelectionSetByType value) Source #
Get the selection set within a field.
type ResponseKey = Name Source #
A ResponseKey
is the key under which a field appears in a response. If
there's an alias, it's the alias, if not, it's the field name.
getResponseKey :: Field' spread value -> ResponseKey Source #
Get the response key of a field.
"A field’s response key is its alias if an alias is provided, and it is otherwise the field’s name."
Exported for testing
findDuplicates :: Ord a => [a] -> [a] Source #
Return a list of all the elements with duplicates. The list of duplicates itself will not contain duplicates.
\xs -> findDuplicates @Int xs == ordNub (findDuplicates @Int xs)
formatErrors :: [ValidationError] -> [Text] Source #
Utility function for tests, format ErrorTypes to their text representation returns a list of error messages