{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveFoldable #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE KindSignatures #-}
{-# OPTIONS_HADDOCK not-home #-}
module GraphQL.Internal.Validation
( ValidationError(..)
, ValidationErrors
, QueryDocument(..)
, validate
, getErrors
, Operation
, getSelectionSet
, VariableDefinition(..)
, VariableValue
, Variable
, AST.GType(..)
, SelectionSetByType
, SelectionSet(..)
, getSelectionSetForType
, Field
, lookupArgument
, getSubSelectionSet
, ResponseKey
, getResponseKey
, findDuplicates
, formatErrors
) where
import Protolude hiding ((<>), throwE)
import Data.List.NonEmpty (NonEmpty(..))
import qualified Data.List.NonEmpty as NonEmpty
import qualified Data.Map as Map
import Data.Semigroup ((<>))
import qualified Data.Set as Set
import GraphQL.Internal.Name (HasName(..), Name)
import qualified GraphQL.Internal.Syntax.AST as AST
import GraphQL.Internal.Syntax.AST (Alias, Variable, NamedType(..))
import GraphQL.Internal.OrderedMap (OrderedMap)
import qualified GraphQL.Internal.OrderedMap as OrderedMap
import GraphQL.Internal.Output (GraphQLError(..))
import GraphQL.Internal.Schema
( TypeDefinition
, ObjectTypeDefinition
, Schema
, doesFragmentTypeApply
, lookupType
, AnnotatedType(..)
, InputType (BuiltinInputType, DefinedInputType)
, AnnotatedType
, getInputTypeDefinition
, builtinFromName
, astAnnotationToSchemaAnnotation
)
import GraphQL.Value
( Value
, Value'
, ConstScalar
, UnresolvedVariableValue
, astToVariableValue
)
data QueryDocument value
= LoneAnonymousOperation (Operation value)
| MultipleOperations (Operations value)
deriving (Eq, Show)
data OperationType
= Mutation
| Query
deriving (Eq, Show)
data Operation value
= Operation OperationType VariableDefinitions (Directives value) (SelectionSetByType value)
deriving (Eq, Show)
instance Functor Operation where
fmap f (Operation operationType vars directives selectionSet)
= Operation operationType vars (fmap f directives) (fmap f selectionSet)
instance Foldable Operation where
foldMap f (Operation _ _ directives selectionSet)
= foldMap f directives `mappend` foldMap f selectionSet
instance Traversable Operation where
traverse f (Operation operationType vars directives selectionSet)
= Operation operationType vars <$> traverse f directives <*> traverse f selectionSet
getSelectionSet :: Operation value -> SelectionSetByType value
getSelectionSet (Operation _ _ _ ss) = ss
type OperationBuilder value = VariableDefinitions -> Directives value -> SelectionSetByType value -> Operation value
type Operations value = Map (Maybe Name) (Operation value)
validate :: Schema -> AST.QueryDocument -> Either (NonEmpty ValidationError) (QueryDocument VariableValue)
validate schema (AST.QueryDocument defns) = runValidator $ do
let (operations, fragments) = splitBy splitDefns defns
let (anonymous, maybeNamed) = splitBy splitOps operations
(frags, visitedFrags) <- resolveFragmentDefinitions =<< validateFragmentDefinitions schema fragments
case (anonymous, maybeNamed) of
([], ops) -> do
(validOps, usedFrags) <- runStateT (validateOperations schema frags ops) mempty
assertAllFragmentsUsed frags (visitedFrags <> usedFrags)
resolvedOps <- traverse validateOperation validOps
pure (MultipleOperations resolvedOps)
([x], []) -> do
(ss, usedFrags) <- runStateT (validateSelectionSet schema frags x) mempty
assertAllFragmentsUsed frags (visitedFrags <> usedFrags)
validValuesSS <- validateValues ss
resolvedValuesSS <- resolveVariables emptyVariableDefinitions validValuesSS
pure (LoneAnonymousOperation (Operation Query emptyVariableDefinitions emptyDirectives resolvedValuesSS))
_ -> throwE (MixedAnonymousOperations (length anonymous) (map fst maybeNamed))
where
splitBy :: (a -> Either b c) -> [a] -> ([b], [c])
splitBy f xs = partitionEithers (map f xs)
splitDefns (AST.DefinitionOperation op) = Left op
splitDefns (AST.DefinitionFragment frag) = Right frag
splitOps (AST.AnonymousQuery ss) = Left ss
splitOps (AST.Query node@(AST.Node maybeName _ _ _)) = Right (maybeName, (Operation Query, node))
splitOps (AST.Mutation node@(AST.Node maybeName _ _ _)) = Right (maybeName, (Operation Mutation, node))
assertAllFragmentsUsed :: Fragments value -> Set (Maybe Name) -> Validation ()
assertAllFragmentsUsed fragments used =
let unused = Set.map pure (Map.keysSet fragments) `Set.difference` used
in unless (Set.null unused) (throwE (UnusedFragments unused))
validateOperations :: Schema -> Fragments AST.Value -> [(Maybe Name, (OperationBuilder AST.Value, AST.Node))] -> StateT (Set (Maybe Name)) Validation (Operations AST.Value)
validateOperations schema fragments ops = do
deduped <- lift (mapErrors DuplicateOperation (makeMap ops))
traverse validateNode deduped
where
validateNode (operationBuilder, AST.Node _ vars directives ss) =
operationBuilder <$> lift (validateVariableDefinitions schema vars)
<*> lift (validateDirectives directives)
<*> validateSelectionSet schema fragments ss
validateOperation :: Operation AST.Value -> Validation (Operation VariableValue)
validateOperation (Operation operationType vars directives selectionSet) = do
validValues <- Operation operationType vars <$> validateValues directives <*> validateValues selectionSet
let usedVariables = getVariables validValues
let definedVariables = getDefinedVariables vars
let unusedVariables = definedVariables `Set.difference` usedVariables
unless (Set.null unusedVariables) $ throwE (UnusedVariables unusedVariables)
resolveVariables vars validValues
validateSelectionSet :: Schema -> Fragments AST.Value -> [AST.Selection] -> StateT (Set (Maybe Name)) Validation (SelectionSetByType AST.Value)
validateSelectionSet schema fragments selections = do
unresolved <- lift $ traverse (validateSelection schema) selections
resolved <- traverse (resolveSelection fragments) unresolved
lift $ groupByResponseKey resolved
newtype SelectionSet value = SelectionSet (OrderedMap ResponseKey (Field value)) deriving (Eq, Ord, Show)
newtype SelectionSetByType value
= SelectionSetByType (OrderedMap ResponseKey (OrderedMap (Set TypeDefinition) (Field value)))
deriving (Eq, Ord, Show, Functor, Foldable, Traversable)
type ResponseKey = Name
data Field value
= Field
{ name :: Name
, arguments :: Arguments value
, subSelectionSet :: Maybe (SelectionSetByType value)
} deriving (Eq, Ord, Show, Functor, Foldable, Traversable)
instance HasName (Field value) where
getName = name
lookupArgument :: Field value -> Name -> Maybe value
lookupArgument (Field _ (Arguments args) _) name = Map.lookup name args
getSubSelectionSet :: Field value -> Maybe (SelectionSetByType value)
getSubSelectionSet = subSelectionSet
mergeFields :: Eq value => Field value -> Field value -> Validation (Field value)
mergeFields field1 field2 = do
unless (name field1 == name field2) $ throwE (MismatchedNames (name field1) (name field2))
unless (arguments field1 == arguments field2) $ throwE (MismatchedArguments (name field1))
case (subSelectionSet field1, subSelectionSet field2) of
(Nothing, Nothing) ->
pure Field { name = name field1
, arguments = arguments field1
, subSelectionSet = Nothing
}
(Just ss1, Just ss2) -> do
mergedSet <- mergeSelectionSets ss1 ss2
pure Field { name = name field1
, arguments = arguments field1
, subSelectionSet = Just mergedSet
}
_ -> throwE (IncompatibleFields (name field1))
where
mergeSelectionSets :: Eq value
=> SelectionSetByType value
-> SelectionSetByType value
-> Validation (SelectionSetByType value)
mergeSelectionSets (SelectionSetByType ss1) (SelectionSetByType ss2) =
SelectionSetByType <$> OrderedMap.unionWithM (OrderedMap.unionWithM mergeFields) ss1 ss2
getSelectionSetForType
:: Eq value
=> ObjectTypeDefinition
-> SelectionSetByType value
-> Either ValidationErrors (SelectionSet value)
getSelectionSetForType objectType (SelectionSetByType ss) = runValidator $
SelectionSet . OrderedMap.catMaybes <$> traverse mergeFieldsForType ss
where
mergeFieldsForType fieldMap = do
let matching = filter (satisfiesType . fst) (OrderedMap.toList fieldMap)
case map snd matching of
[] -> pure Nothing
x:xs -> Just <$> foldlM mergeFields x xs
satisfiesType = all (doesFragmentTypeApply objectType) . Set.toList
groupByResponseKey :: Eq value => [Selection' FragmentSpread value] -> Validation (SelectionSetByType value)
groupByResponseKey selectionSet = SelectionSetByType <$>
flattenSelectionSet mempty selectionSet
where
byKey :: Eq value
=> Set TypeDefinition
-> Selection' FragmentSpread value
-> Validation (OrderedMap ResponseKey (OrderedMap (Set TypeDefinition) (Field value)))
byKey typeConds (SelectionField field@(Field' _ name arguments _ ss))
= case ss of
[] -> pure $ OrderedMap.singleton (getResponseKey field) . OrderedMap.singleton typeConds . Field name arguments $ Nothing
_ -> OrderedMap.singleton (getResponseKey field) . OrderedMap.singleton typeConds . Field name arguments . Just <$> groupByResponseKey ss
byKey typeConds (SelectionFragmentSpread (FragmentSpread _ _ (FragmentDefinition _ typeCond _ ss)))
= flattenSelectionSet (typeConds <> Set.singleton typeCond) ss
byKey typeConds (SelectionInlineFragment (InlineFragment (Just typeCond) _ ss))
= flattenSelectionSet (typeConds <> Set.singleton typeCond) ss
byKey typeConds (SelectionInlineFragment (InlineFragment Nothing _ ss))
= flattenSelectionSet typeConds ss
flattenSelectionSet :: Eq value
=> Set TypeDefinition
-> [Selection' FragmentSpread value]
-> Validation (OrderedMap ResponseKey (OrderedMap (Set TypeDefinition) (Field value)))
flattenSelectionSet typeConds ss = do
groupedByKey <- traverse (byKey typeConds) ss
OrderedMap.unionsWithM (OrderedMap.unionWithM mergeFields) groupedByKey
data Selection' (spread :: * -> *) value
= SelectionField (Field' spread value)
| SelectionFragmentSpread (spread value)
| SelectionInlineFragment (InlineFragment spread value)
deriving (Eq, Show, Functor, Foldable, Traversable)
data Field' spread value
= Field' (Maybe Alias) Name (Arguments value) (Directives value) [Selection' spread value]
deriving (Eq, Show)
getResponseKey :: Field' spread value -> ResponseKey
getResponseKey (Field' alias name _ _ _) = fromMaybe name alias
instance HasName (Field' spread value) where
getName (Field' _ name _ _ _) = name
instance Functor spread => Functor (Field' spread) where
fmap f (Field' alias name arguments directives selectionSet) =
Field' alias name (fmap f arguments) (fmap f directives) (map (fmap f) selectionSet)
instance Foldable spread => Foldable (Field' spread) where
foldMap f (Field' _ _ arguments directives selectionSet) =
mconcat [ foldMap f arguments
, foldMap f directives
, mconcat (map (foldMap f) selectionSet)
]
instance Traversable spread => Traversable (Field' spread) where
traverse f (Field' alias name arguments directives selectionSet) =
Field' alias name <$> traverse f arguments
<*> traverse f directives
<*> traverse (traverse f) selectionSet
data UnresolvedFragmentSpread value
= UnresolvedFragmentSpread Name (Directives value)
deriving (Eq, Show, Functor)
instance Foldable UnresolvedFragmentSpread where
foldMap f (UnresolvedFragmentSpread _ directives) = foldMap f directives
instance Traversable UnresolvedFragmentSpread where
traverse f (UnresolvedFragmentSpread name directives) = UnresolvedFragmentSpread name <$> traverse f directives
data FragmentSpread value
= FragmentSpread Name (Directives value) (FragmentDefinition FragmentSpread value)
deriving (Eq, Show)
instance Functor FragmentSpread where
fmap f (FragmentSpread name directives definition) = FragmentSpread name (fmap f directives) (fmap f definition)
instance Foldable FragmentSpread where
foldMap f (FragmentSpread _ directives fragment) = foldMap f directives `mappend` foldMap f fragment
instance Traversable FragmentSpread where
traverse f (FragmentSpread name directives definition) =
FragmentSpread name <$> traverse f directives <*> traverse f definition
data InlineFragment spread value
= InlineFragment (Maybe TypeDefinition) (Directives value) [Selection' spread value]
deriving (Eq, Show)
instance Functor spread => Functor (InlineFragment spread) where
fmap f (InlineFragment typeDefn directives selectionSet) =
InlineFragment typeDefn (fmap f directives) (map (fmap f) selectionSet)
instance Foldable spread => Foldable (InlineFragment spread) where
foldMap f (InlineFragment _ directives selectionSet) =
foldMap f directives `mappend` mconcat (map (foldMap f) selectionSet)
instance Traversable spread => Traversable (InlineFragment spread) where
traverse f (InlineFragment typeDefn directives selectionSet) =
InlineFragment typeDefn <$> traverse f directives
<*> traverse (traverse f) selectionSet
traverseFragmentSpreads :: Applicative f => (a value -> f (b value)) -> Selection' a value -> f (Selection' b value)
traverseFragmentSpreads f selection =
case selection of
SelectionField (Field' alias name args directives ss) ->
SelectionField <$> (Field' alias name args directives <$> childSegments ss)
SelectionFragmentSpread x ->
SelectionFragmentSpread <$> f x
SelectionInlineFragment (InlineFragment typeCond directives ss) ->
SelectionInlineFragment <$> (InlineFragment typeCond directives <$> childSegments ss)
where
childSegments = traverse (traverseFragmentSpreads f)
validateSelection :: Schema -> AST.Selection -> Validation (Selection' UnresolvedFragmentSpread AST.Value)
validateSelection schema selection =
case selection of
AST.SelectionField (AST.Field alias name args directives ss) ->
SelectionField <$> (Field' alias name
<$> validateArguments args
<*> validateDirectives directives
<*> childSegments ss)
AST.SelectionFragmentSpread (AST.FragmentSpread name directives) ->
SelectionFragmentSpread <$> (UnresolvedFragmentSpread name <$> validateDirectives directives)
AST.SelectionInlineFragment (AST.InlineFragment typeCond directives ss) ->
SelectionInlineFragment <$> (InlineFragment
<$> traverse (validateTypeCondition schema) typeCond
<*> validateDirectives directives
<*> childSegments ss)
where
childSegments = traverse (validateSelection schema)
resolveSelection :: Fragments a -> Selection' UnresolvedFragmentSpread a -> StateT (Set (Maybe Name)) Validation (Selection' FragmentSpread a)
resolveSelection fragments = traverseFragmentSpreads resolveFragmentSpread
where
resolveFragmentSpread (UnresolvedFragmentSpread name directive) = do
case Map.lookup name fragments of
Nothing -> lift (throwE (NoSuchFragment name))
Just fragment -> do
modify (Set.insert (pure name))
pure (FragmentSpread name directive fragment)
data FragmentDefinition spread value
= FragmentDefinition Name TypeDefinition (Directives value) [Selection' spread value]
deriving (Eq, Show)
type Fragments value = Map Name (FragmentDefinition FragmentSpread value)
instance Functor spread => Functor (FragmentDefinition spread) where
fmap f (FragmentDefinition name typeDefn directives selectionSet) =
FragmentDefinition name typeDefn (fmap f directives) (map (fmap f) selectionSet)
instance Foldable spread => Foldable (FragmentDefinition spread) where
foldMap f (FragmentDefinition _ _ directives selectionSet) =
foldMap f directives `mappend` mconcat (map (foldMap f) selectionSet)
instance Traversable spread => Traversable (FragmentDefinition spread) where
traverse f (FragmentDefinition name typeDefn directives selectionSet) =
FragmentDefinition name typeDefn <$> traverse f directives
<*> traverse (traverse f) selectionSet
validateFragmentDefinitions :: Schema -> [AST.FragmentDefinition] -> Validation (Map Name (FragmentDefinition UnresolvedFragmentSpread AST.Value))
validateFragmentDefinitions schema frags = do
defns <- traverse validateFragmentDefinition frags
mapErrors DuplicateFragmentDefinition (makeMap [(name, value) | value@(FragmentDefinition name _ _ _) <- defns])
where
validateFragmentDefinition (AST.FragmentDefinition name typeCond directives ss) = do
FragmentDefinition name
<$> validateTypeCondition schema typeCond
<*> validateDirectives directives
<*> traverse (validateSelection schema) ss
validateTypeCondition :: Schema -> AST.TypeCondition -> Validation TypeDefinition
validateTypeCondition schema (NamedType typeCond) =
case lookupType schema typeCond of
Nothing -> throwE (TypeConditionNotFound typeCond)
Just typeDefn -> pure typeDefn
resolveFragmentDefinitions :: Map Name (FragmentDefinition UnresolvedFragmentSpread value) -> Validation (Fragments value, Set (Maybe Name))
resolveFragmentDefinitions allFragments =
splitResult <$> traverse resolveFragment allFragments
where
splitResult mapWithVisited = (map fst mapWithVisited, foldMap snd mapWithVisited)
resolveFragment frag = runStateT (resolveFragment' frag) mempty
resolveFragment' (FragmentDefinition name cond directives ss) =
FragmentDefinition name cond directives <$> traverse (traverseFragmentSpreads resolveSpread) ss
resolveSpread (UnresolvedFragmentSpread name directives) = do
visited <- Set.member (pure name) <$> get
when visited (lift (throwE (CircularFragmentSpread name)))
case Map.lookup name allFragments of
Nothing -> lift (throwE (NoSuchFragment name))
Just definition -> do
modify (Set.insert (pure name))
FragmentSpread name directives <$> resolveFragment' definition
newtype Arguments value = Arguments (Map Name value) deriving (Eq, Ord, Show, Functor, Foldable, Traversable)
validateArguments :: [AST.Argument] -> Validation (Arguments AST.Value)
validateArguments args = Arguments <$> mapErrors DuplicateArgument (makeMap [(name, value) | AST.Argument name value <- args])
data VariableDefinition
= VariableDefinition
{ variable :: Variable
, variableType :: AnnotatedType InputType
, defaultValue :: Maybe Value
} deriving (Eq, Ord, Show)
type VariableDefinitions = Map Variable VariableDefinition
getDefinedVariables :: VariableDefinitions -> Set Variable
getDefinedVariables = Map.keysSet
type VariableValue = Value' (Either VariableDefinition ConstScalar)
emptyVariableDefinitions :: VariableDefinitions
emptyVariableDefinitions = mempty
validateVariableDefinitions :: Schema -> [AST.VariableDefinition] -> Validation VariableDefinitions
validateVariableDefinitions schema vars = do
validatedDefns <- traverse (validateVariableDefinition schema) vars
let items = [ (variable defn, defn) | defn <- validatedDefns]
mapErrors DuplicateVariableDefinition (makeMap items)
validateVariableDefinition :: Schema -> AST.VariableDefinition -> Validation VariableDefinition
validateVariableDefinition schema (AST.VariableDefinition var varType value) =
VariableDefinition var
<$> validateTypeAssertion schema var varType
<*> traverse validateDefaultValue value
validateTypeAssertion :: Schema -> Variable -> AST.GType -> Validation (AnnotatedType InputType)
validateTypeAssertion schema var varTypeAST =
astAnnotationToSchemaAnnotation varTypeAST <$>
case lookupType schema varTypeNameAST of
Nothing -> validateVariableTypeBuiltin var varTypeNameAST
Just cleanTypeDef -> validateVariableTypeDefinition var cleanTypeDef
where
varTypeNameAST = getName varTypeAST
validateVariableTypeDefinition :: Variable -> TypeDefinition -> Validation InputType
validateVariableTypeDefinition var typeDef =
case getInputTypeDefinition typeDef of
Nothing -> throwE (VariableTypeIsNotInputType var $ getName typeDef)
Just value -> pure (DefinedInputType value)
validateVariableTypeBuiltin :: Variable -> Name -> Validation InputType
validateVariableTypeBuiltin var typeName =
case builtinFromName typeName of
Nothing -> throwE (VariableTypeNotFound var typeName)
Just builtin -> pure (BuiltinInputType builtin)
validateDefaultValue :: AST.DefaultValue -> Validation Value
validateDefaultValue defaultValue =
case astToVariableValue defaultValue of
Nothing -> throwE $ InvalidValue defaultValue
Just value ->
for value $
\case
Left _ -> throwE $ InvalidDefaultValue defaultValue
Right constant -> pure constant
getVariables :: Foldable f => f UnresolvedVariableValue -> Set Variable
getVariables = foldMap valueToVariable
where
valueToVariable = foldMap (either Set.singleton (const Set.empty))
validateValues :: Traversable f => f AST.Value -> Validation (f UnresolvedVariableValue)
validateValues = traverse toVariableValue
where
toVariableValue astValue =
case astToVariableValue astValue of
Just value -> pure value
Nothing -> throwE (InvalidValue astValue)
resolveVariables :: Traversable f => VariableDefinitions -> f UnresolvedVariableValue -> Validation (f VariableValue)
resolveVariables definitions = traverse resolveVariableValue
where
resolveVariableValue = traverse resolveVariable
resolveVariable (Left variable) =
case Map.lookup variable definitions of
Nothing -> throwE (UndefinedVariable variable)
Just defn -> pure (Left defn)
resolveVariable (Right constant) = pure (Right constant)
newtype Directives value = Directives (Map Name (Arguments value)) deriving (Eq, Ord, Show, Foldable, Functor, Traversable)
emptyDirectives :: Directives value
emptyDirectives = Directives Map.empty
validateDirectives :: [AST.Directive] -> Validation (Directives AST.Value)
validateDirectives directives = do
items <- traverse validateDirective directives
Directives <$> mapErrors DuplicateDirective (makeMap items)
where
validateDirective (AST.Directive name args) = (,) name <$> validateArguments args
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 AST.Value
| InvalidDefaultValue AST.Value
| MismatchedNames Name Name
| MismatchedArguments Name
| IncompatibleFields Name
| TypeConditionNotFound Name
| VariableTypeNotFound Variable Name
| VariableTypeIsNotInputType Variable Name
deriving (Eq, Show)
instance GraphQLError ValidationError where
formatError (DuplicateOperation maybeName) = "More than one operation named '" <> show maybeName <> "'"
formatError (MixedAnonymousOperations n maybeNames)
| n > 1 && null maybeNames = "Multiple anonymous operations defined. Found " <> show n
| otherwise = "Document contains both anonymous operations (" <> show n <> ") and named operations (" <> show maybeNames <> ")"
formatError (DuplicateArgument name) = "More than one argument named '" <> show name <> "'"
formatError (DuplicateFragmentDefinition name) = "More than one fragment named '" <> show name <> "'"
formatError (NoSuchFragment name) = "No fragment named '" <> show name <> "'"
formatError (DuplicateDirective name) = "More than one directive named '" <> show name <> "'"
formatError (DuplicateVariableDefinition name) = "More than one variable defined with name '" <> show name <> "'"
formatError (CircularFragmentSpread name) = "Fragment '" <> show name <> "' contains a fragment spread that refers back to itself."
formatError (UnusedFragments names) = "Fragments defined but not used: " <> show names
formatError (UnusedVariables names) = "Variables defined but not used: " <> show names
formatError (UndefinedVariable variable) = "No definition for variable: " <> show variable
formatError (InvalidValue value) = "Invalid value (maybe an object has duplicate field names?): " <> show value
formatError (InvalidDefaultValue value) = "Invalid default value, contains variables: " <> show value
formatError (MismatchedNames name1 name2) = "Two different names given for same response key: " <> show name1 <> ", " <> show name2
formatError (MismatchedArguments name) = "Two different sets of arguments given for same response key: " <> show name
formatError (IncompatibleFields name) = "Field " <> show name <> " has a leaf in one place and a non-leaf in another."
formatError (TypeConditionNotFound name) = "Type condition " <> show name <> " not found in schema."
formatError (VariableTypeNotFound var name) = "Type named " <> show name <> " for variable " <> show var <> " is not in the schema."
formatError (VariableTypeIsNotInputType var name) = "Type named " <> show name <> " for variable " <> show var <> " is not an input type."
type ValidationErrors = NonEmpty ValidationError
type Validation = Validator ValidationError
getErrors :: Schema -> AST.QueryDocument -> [ValidationError]
getErrors schema doc =
case validate schema doc of
Left errors -> NonEmpty.toList errors
Right _ -> []
findDuplicates :: Ord a => [a] -> [a]
findDuplicates xs = findDups (sort xs)
where
findDups [] = []
findDups [_] = []
findDups (x:ys@(y:zs))
| x == y = x:findDups (dropWhile (== x) zs)
| otherwise = findDups ys
makeMap :: Ord key => [(key, value)] -> Validator key (Map key value)
makeMap entries =
case NonEmpty.nonEmpty (findDuplicates (map fst entries)) of
Nothing -> pure (Map.fromList entries)
Just dups -> throwErrors dups
formatErrors :: [ValidationError] -> [Text]
formatErrors errors = formatError <$> errors
newtype Validator e a = Validator { runValidator :: Either (NonEmpty e) a } deriving (Eq, Show, Functor, Monad)
throwE :: e -> Validator e a
throwE e = throwErrors (e :| [])
throwErrors :: NonEmpty e -> Validator e a
throwErrors = Validator . Left
mapErrors :: (e1 -> e2) -> Validator e1 a -> Validator e2 a
mapErrors f (Validator (Left es)) = Validator (Left (map f es))
mapErrors _ (Validator (Right x)) = Validator (Right x)
instance Applicative (Validator e) where
pure x = Validator (Right x)
Validator (Left e1) <*> (Validator (Left e2)) = Validator (Left (e1 <> e2))
Validator (Left e) <*> _ = Validator (Left e)
Validator _ <*> (Validator (Left e)) = Validator (Left e)
Validator (Right f) <*> Validator (Right x) = Validator (Right (f x))