graphql-api-0.2.0: Sketch of GraphQL stuff

Safe HaskellNone
LanguageHaskell2010

GraphQL.Internal.Validation

Contents

Description

Transform GraphQL query documents from AST into valid structures

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:

Because all of the above rely on type checking.

Synopsis

Documentation

data ValidationError Source #

Errors arising from validating a document.

Constructors

DuplicateOperation Name

DuplicateOperation means there was more than one operation defined with the given name.

https://facebook.github.io/graphql/#sec-Operation-Name-Uniqueness

MixedAnonymousOperations Int [Name]

MixedAnonymousOperations means there was more than one operation defined in a document with an anonymous operation.

https://facebook.github.io/graphql/#sec-Lone-Anonymous-Operation

DuplicateArgument Name

DuplicateArgument means that multiple copies of the same argument was given to the same field, directive, etc.

DuplicateFragmentDefinition Name

DuplicateFragmentDefinition means that there were more than one fragment defined with the same name.

NoSuchFragment Name

NoSuchFragment means there was a reference to a fragment in a fragment spread but we couldn't find any fragment with that name.

DuplicateDirective Name

DuplicateDirective means there were two copies of the same directive given in the same place.

https://facebook.github.io/graphql/#sec-Directives-Are-Unique-Per-Location

DuplicateVariableDefinition Variable

There were multiple variables defined with the same name.

CircularFragmentSpread Name

CircularFragmentSpread means that a fragment definition contains a fragment spread that itself is a fragment definition that contains a fragment spread referring to the first fragment spread.

UnusedFragments (Set Name)

UnusedFragments means that fragments were defined that weren't used. https://facebook.github.io/graphql/#sec-Fragments-Must-Be-Used

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.

data QueryDocument value Source #

A valid query document.

Construct this using validate on an QueryDocument.

Constructors

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 # 

Methods

(==) :: QueryDocument value -> QueryDocument value -> Bool #

(/=) :: QueryDocument value -> QueryDocument value -> Bool #

Show value => Show (QueryDocument value) Source # 

Methods

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.

https://facebook.github.io/graphql/#sec-Validation

Operating on validated documents

data Operation value Source #

Instances

Functor Operation Source # 

Methods

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

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

Foldable Operation Source # 

Methods

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] #

null :: Operation a -> Bool #

length :: Operation a -> Int #

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

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

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

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

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

Traversable Operation Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Operation a -> f (Operation b) #

sequenceA :: Applicative f => Operation (f a) -> f (Operation a) #

mapM :: Monad m => (a -> m b) -> Operation a -> m (Operation b) #

sequence :: Monad m => Operation (m a) -> m (Operation a) #

Eq value => Eq (Operation value) Source # 

Methods

(==) :: Operation value -> Operation value -> Bool #

(/=) :: Operation value -> Operation value -> Bool #

Show value => Show (Operation value) Source # 

Methods

showsPrec :: Int -> Operation value -> ShowS #

show :: Operation value -> String #

showList :: [Operation value] -> ShowS #

getSelectionSet :: Operation value -> SelectionSetByType value Source #

Get the selection set for an operation.

Executing validated documents

type VariableValue = Value' (Either VariableDefinition ConstScalar) Source #

A GraphQL value which might contain some defined variables.

data Type Source #

Instances

Eq Type Source # 

Methods

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

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

Ord Type Source # 

Methods

compare :: Type -> Type -> Ordering #

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

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

(>) :: Type -> Type -> Bool #

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

max :: Type -> Type -> Type #

min :: Type -> Type -> Type #

Show Type Source # 

Methods

showsPrec :: Int -> Type -> ShowS #

show :: Type -> String #

showList :: [Type] -> ShowS #

Resolving queries

data SelectionSetByType value Source #

Instances

Functor SelectionSetByType Source # 
Foldable SelectionSetByType Source # 

Methods

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

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

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

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

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

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

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

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

toList :: SelectionSetByType a -> [a] #

null :: SelectionSetByType a -> Bool #

length :: SelectionSetByType a -> Int #

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

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

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

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

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

Traversable SelectionSetByType Source # 
Eq value => Eq (SelectionSetByType value) Source # 
Ord value => Ord (SelectionSetByType value) Source # 
Show value => Show (SelectionSetByType value) Source # 

newtype SelectionSet value Source #

A selection set, almost fully validated.

Sub-selection sets might not be validated.

Constructors

SelectionSet (OrderedMap ResponseKey (Field value)) 

Instances

Eq value => Eq (SelectionSet value) Source # 

Methods

(==) :: SelectionSet value -> SelectionSet value -> Bool #

(/=) :: SelectionSet value -> SelectionSet value -> Bool #

Ord value => Ord (SelectionSet value) Source # 

Methods

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 # 

Methods

showsPrec :: Int -> SelectionSet value -> ShowS #

show :: SelectionSet value -> String #

showList :: [SelectionSet value] -> ShowS #

getSelectionSetForType Source #

Arguments

:: 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.

data Field value Source #

A field ready to be resolved.

Instances

Functor Field Source # 

Methods

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

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

Foldable Field Source # 

Methods

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 #

toList :: Field a -> [a] #

null :: Field a -> Bool #

length :: Field a -> Int #

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

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

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

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

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

Traversable Field Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Field a -> f (Field b) #

sequenceA :: Applicative f => Field (f a) -> f (Field a) #

mapM :: Monad m => (a -> m b) -> Field a -> m (Field b) #

sequence :: Monad m => Field (m a) -> m (Field a) #

Eq value => Eq (Field value) Source # 

Methods

(==) :: Field value -> Field value -> Bool #

(/=) :: Field value -> Field value -> Bool #

Ord value => Ord (Field value) Source # 

Methods

compare :: Field value -> Field value -> Ordering #

(<) :: Field value -> Field value -> Bool #

(<=) :: Field value -> Field value -> Bool #

(>) :: Field value -> Field value -> Bool #

(>=) :: Field value -> Field value -> Bool #

max :: Field value -> Field value -> Field value #

min :: Field value -> Field value -> Field value #

Show value => Show (Field value) Source # 

Methods

showsPrec :: Int -> Field value -> ShowS #

show :: Field value -> String #

showList :: [Field value] -> ShowS #

HasName (Field value) Source # 

Methods

getName :: Field value -> Name 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."

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

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)