2020-07-20 21:29:12 +02:00
|
|
|
|
{- This Source Code Form is subject to the terms of the Mozilla Public License,
|
|
|
|
|
v. 2.0. If a copy of the MPL was not distributed with this file, You can
|
|
|
|
|
obtain one at https://mozilla.org/MPL/2.0/. -}
|
|
|
|
|
|
2020-08-25 21:03:42 +02:00
|
|
|
|
{-# LANGUAGE ExplicitForAll #-}
|
2020-08-26 18:58:48 +02:00
|
|
|
|
{-# LANGUAGE LambdaCase #-}
|
2020-08-25 21:03:42 +02:00
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
2020-08-27 09:04:31 +02:00
|
|
|
|
{-# LANGUAGE ViewPatterns #-}
|
2020-08-25 21:03:42 +02:00
|
|
|
|
|
2020-07-24 21:34:31 +02:00
|
|
|
|
-- | This module contains default rules defined in the GraphQL specification.
|
2020-07-20 21:29:12 +02:00
|
|
|
|
module Language.GraphQL.Validate.Rules
|
2020-08-25 21:03:42 +02:00
|
|
|
|
( executableDefinitionsRule
|
2020-09-07 22:01:49 +02:00
|
|
|
|
, fragmentsOnCompositeTypesRule
|
2020-09-04 19:12:19 +02:00
|
|
|
|
, fragmentSpreadTargetDefinedRule
|
|
|
|
|
, fragmentSpreadTypeExistenceRule
|
2020-08-27 09:04:31 +02:00
|
|
|
|
, loneAnonymousOperationRule
|
2020-09-09 17:04:31 +02:00
|
|
|
|
, noUnusedFragmentsRule
|
2020-08-27 09:04:31 +02:00
|
|
|
|
, singleFieldSubscriptionsRule
|
2020-07-20 21:29:12 +02:00
|
|
|
|
, specifiedRules
|
2020-08-28 08:32:21 +02:00
|
|
|
|
, uniqueFragmentNamesRule
|
2020-08-27 09:04:31 +02:00
|
|
|
|
, uniqueOperationNamesRule
|
2020-07-20 21:29:12 +02:00
|
|
|
|
) where
|
|
|
|
|
|
2020-08-25 21:03:42 +02:00
|
|
|
|
import Control.Monad (foldM)
|
|
|
|
|
import Control.Monad.Trans.Class (MonadTrans(..))
|
|
|
|
|
import Control.Monad.Trans.Reader (asks)
|
|
|
|
|
import Control.Monad.Trans.State (evalStateT, gets, modify)
|
2020-08-31 11:06:27 +02:00
|
|
|
|
import Data.Foldable (find)
|
2020-09-04 19:12:19 +02:00
|
|
|
|
import qualified Data.HashMap.Strict as HashMap
|
2020-08-25 21:03:42 +02:00
|
|
|
|
import qualified Data.HashSet as HashSet
|
2020-09-04 19:12:19 +02:00
|
|
|
|
import Data.Text (Text)
|
2020-08-25 21:03:42 +02:00
|
|
|
|
import qualified Data.Text as Text
|
2020-07-20 21:29:12 +02:00
|
|
|
|
import Language.GraphQL.AST.Document
|
2020-08-25 21:03:42 +02:00
|
|
|
|
import Language.GraphQL.Type.Internal
|
|
|
|
|
import qualified Language.GraphQL.Type.Schema as Schema
|
|
|
|
|
import Language.GraphQL.Validate.Validation
|
2020-07-20 21:29:12 +02:00
|
|
|
|
|
2020-08-22 06:39:52 +02:00
|
|
|
|
-- | Default rules given in the specification.
|
2020-08-25 21:03:42 +02:00
|
|
|
|
specifiedRules :: forall m. [Rule m]
|
2020-07-20 21:29:12 +02:00
|
|
|
|
specifiedRules =
|
2020-09-04 19:12:19 +02:00
|
|
|
|
-- Documents.
|
2020-07-20 21:29:12 +02:00
|
|
|
|
[ executableDefinitionsRule
|
2020-09-04 19:12:19 +02:00
|
|
|
|
-- Operations.
|
2020-08-25 21:03:42 +02:00
|
|
|
|
, singleFieldSubscriptionsRule
|
2020-08-26 18:58:48 +02:00
|
|
|
|
, loneAnonymousOperationRule
|
2020-08-27 09:04:31 +02:00
|
|
|
|
, uniqueOperationNamesRule
|
2020-09-04 19:12:19 +02:00
|
|
|
|
-- Fragments.
|
2020-08-28 08:32:21 +02:00
|
|
|
|
, uniqueFragmentNamesRule
|
2020-09-04 19:12:19 +02:00
|
|
|
|
, fragmentSpreadTypeExistenceRule
|
2020-09-07 22:01:49 +02:00
|
|
|
|
, fragmentsOnCompositeTypesRule
|
2020-09-09 17:04:31 +02:00
|
|
|
|
, noUnusedFragmentsRule
|
|
|
|
|
, fragmentSpreadTargetDefinedRule
|
2020-07-20 21:29:12 +02:00
|
|
|
|
]
|
|
|
|
|
|
2020-07-24 21:34:31 +02:00
|
|
|
|
-- | Definition must be OperationDefinition or FragmentDefinition.
|
2020-08-25 21:03:42 +02:00
|
|
|
|
executableDefinitionsRule :: forall m. Rule m
|
2020-08-26 18:58:48 +02:00
|
|
|
|
executableDefinitionsRule = DefinitionRule $ \case
|
|
|
|
|
ExecutableDefinition _ -> lift Nothing
|
2020-08-27 09:04:31 +02:00
|
|
|
|
TypeSystemDefinition _ location -> pure $ error' location
|
|
|
|
|
TypeSystemExtension _ location -> pure $ error' location
|
|
|
|
|
where
|
|
|
|
|
error' location = Error
|
|
|
|
|
{ message =
|
|
|
|
|
"Definition must be OperationDefinition or FragmentDefinition."
|
|
|
|
|
, locations = [location]
|
|
|
|
|
, path = []
|
|
|
|
|
}
|
2020-08-25 21:03:42 +02:00
|
|
|
|
|
|
|
|
|
-- | Subscription operations must have exactly one root field.
|
|
|
|
|
singleFieldSubscriptionsRule :: forall m. Rule m
|
2020-08-26 18:58:48 +02:00
|
|
|
|
singleFieldSubscriptionsRule = OperationDefinitionRule $ \case
|
2020-08-27 09:04:31 +02:00
|
|
|
|
OperationDefinition Subscription name' _ _ rootFields location -> do
|
2020-08-25 21:03:42 +02:00
|
|
|
|
groupedFieldSet <- evalStateT (collectFields rootFields) HashSet.empty
|
|
|
|
|
case HashSet.size groupedFieldSet of
|
|
|
|
|
1 -> lift Nothing
|
|
|
|
|
_
|
2020-08-27 09:04:31 +02:00
|
|
|
|
| Just name <- name' -> pure $ Error
|
|
|
|
|
{ message = unwords
|
|
|
|
|
[ "Subscription"
|
|
|
|
|
, Text.unpack name
|
|
|
|
|
, "must select only one top level field."
|
|
|
|
|
]
|
|
|
|
|
, locations = [location]
|
|
|
|
|
, path = []
|
|
|
|
|
}
|
|
|
|
|
| otherwise -> pure $ Error
|
|
|
|
|
{ message = errorMessage
|
|
|
|
|
, locations = [location]
|
|
|
|
|
, path = []
|
|
|
|
|
}
|
2020-08-26 18:58:48 +02:00
|
|
|
|
_ -> lift Nothing
|
|
|
|
|
where
|
2020-08-27 09:04:31 +02:00
|
|
|
|
errorMessage =
|
|
|
|
|
"Anonymous Subscription must select only one top level field."
|
2020-08-25 21:03:42 +02:00
|
|
|
|
collectFields selectionSet = foldM forEach HashSet.empty selectionSet
|
2020-09-07 22:01:49 +02:00
|
|
|
|
forEach accumulator = \case
|
2020-09-09 17:04:31 +02:00
|
|
|
|
FieldSelection fieldSelection -> forField accumulator fieldSelection
|
2020-09-07 22:01:49 +02:00
|
|
|
|
FragmentSpreadSelection fragmentSelection ->
|
|
|
|
|
forSpread accumulator fragmentSelection
|
|
|
|
|
InlineFragmentSelection fragmentSelection ->
|
|
|
|
|
forInline accumulator fragmentSelection
|
2020-09-09 17:04:31 +02:00
|
|
|
|
forField accumulator (Field alias name _ directives _ _)
|
|
|
|
|
| any skip directives = pure accumulator
|
|
|
|
|
| Just aliasedName <- alias = pure
|
|
|
|
|
$ HashSet.insert aliasedName accumulator
|
|
|
|
|
| otherwise = pure $ HashSet.insert name accumulator
|
2020-09-07 22:01:49 +02:00
|
|
|
|
forSpread accumulator (FragmentSpread fragmentName directives _)
|
2020-08-25 21:03:42 +02:00
|
|
|
|
| any skip directives = pure accumulator
|
|
|
|
|
| otherwise = do
|
|
|
|
|
inVisitetFragments <- gets $ HashSet.member fragmentName
|
|
|
|
|
if inVisitetFragments
|
|
|
|
|
then pure accumulator
|
|
|
|
|
else collectFromSpread fragmentName accumulator
|
2020-09-07 22:01:49 +02:00
|
|
|
|
forInline accumulator (InlineFragment maybeType directives selections _)
|
2020-08-25 21:03:42 +02:00
|
|
|
|
| any skip directives = pure accumulator
|
2020-09-07 22:01:49 +02:00
|
|
|
|
| Just typeCondition <- maybeType =
|
|
|
|
|
collectFromFragment typeCondition selections accumulator
|
2020-08-25 21:03:42 +02:00
|
|
|
|
| otherwise = HashSet.union accumulator
|
2020-09-07 22:01:49 +02:00
|
|
|
|
<$> collectFields selections
|
2020-08-25 21:03:42 +02:00
|
|
|
|
skip (Directive "skip" [Argument "if" (Boolean True)]) = True
|
|
|
|
|
skip (Directive "include" [Argument "if" (Boolean False)]) = True
|
|
|
|
|
skip _ = False
|
|
|
|
|
findFragmentDefinition (ExecutableDefinition executableDefinition) Nothing
|
|
|
|
|
| DefinitionFragment fragmentDefinition <- executableDefinition =
|
|
|
|
|
Just fragmentDefinition
|
|
|
|
|
findFragmentDefinition _ accumulator = accumulator
|
|
|
|
|
collectFromFragment typeCondition selectionSet accumulator = do
|
|
|
|
|
types' <- lift $ asks types
|
|
|
|
|
schema' <- lift $ asks schema
|
|
|
|
|
case lookupTypeCondition typeCondition types' of
|
|
|
|
|
Nothing -> pure accumulator
|
|
|
|
|
Just compositeType
|
|
|
|
|
| Just objectType <- Schema.subscription schema'
|
|
|
|
|
, True <- doesFragmentTypeApply compositeType objectType ->
|
2020-09-09 17:04:31 +02:00
|
|
|
|
HashSet.union accumulator <$> collectFields selectionSet
|
2020-08-25 21:03:42 +02:00
|
|
|
|
| otherwise -> pure accumulator
|
|
|
|
|
collectFromSpread fragmentName accumulator = do
|
|
|
|
|
modify $ HashSet.insert fragmentName
|
|
|
|
|
ast' <- lift $ asks ast
|
|
|
|
|
case foldr findFragmentDefinition Nothing ast' of
|
|
|
|
|
Nothing -> pure accumulator
|
|
|
|
|
Just (FragmentDefinition _ typeCondition _ selectionSet _) ->
|
|
|
|
|
collectFromFragment typeCondition selectionSet accumulator
|
2020-08-26 18:58:48 +02:00
|
|
|
|
|
|
|
|
|
-- | GraphQL allows a short‐hand form for defining query operations when only
|
|
|
|
|
-- that one operation exists in the document.
|
|
|
|
|
loneAnonymousOperationRule :: forall m. Rule m
|
|
|
|
|
loneAnonymousOperationRule = OperationDefinitionRule $ \case
|
|
|
|
|
SelectionSet _ thisLocation -> check thisLocation
|
|
|
|
|
OperationDefinition _ Nothing _ _ _ thisLocation -> check thisLocation
|
|
|
|
|
_ -> lift Nothing
|
|
|
|
|
where
|
|
|
|
|
check thisLocation = asks ast
|
2020-08-27 09:04:31 +02:00
|
|
|
|
>>= lift . foldr (filterAnonymousOperations thisLocation) Nothing
|
2020-08-26 18:58:48 +02:00
|
|
|
|
filterAnonymousOperations thisLocation definition Nothing
|
2020-08-27 09:04:31 +02:00
|
|
|
|
| (viewOperation -> Just operationDefinition) <- definition =
|
2020-08-26 18:58:48 +02:00
|
|
|
|
compareAnonymousOperations thisLocation operationDefinition
|
|
|
|
|
filterAnonymousOperations _ _ accumulator = accumulator
|
2020-08-27 09:04:31 +02:00
|
|
|
|
compareAnonymousOperations thisLocation = \case
|
|
|
|
|
OperationDefinition _ _ _ _ _ thatLocation
|
|
|
|
|
| thisLocation /= thatLocation -> pure $ error' thisLocation
|
|
|
|
|
SelectionSet _ thatLocation
|
|
|
|
|
| thisLocation /= thatLocation -> pure $ error' thisLocation
|
|
|
|
|
_ -> Nothing
|
|
|
|
|
error' location = Error
|
|
|
|
|
{ message =
|
|
|
|
|
"This anonymous operation must be the only defined operation."
|
|
|
|
|
, locations = [location]
|
|
|
|
|
, path = []
|
|
|
|
|
}
|
|
|
|
|
|
|
|
|
|
-- | Each named operation definition must be unique within a document when
|
|
|
|
|
-- referred to by its name.
|
|
|
|
|
uniqueOperationNamesRule :: forall m. Rule m
|
|
|
|
|
uniqueOperationNamesRule = OperationDefinitionRule $ \case
|
2020-08-28 08:32:21 +02:00
|
|
|
|
OperationDefinition _ (Just thisName) _ _ _ thisLocation ->
|
|
|
|
|
findDuplicates (filterByName thisName) thisLocation (error' thisName)
|
2020-08-27 09:04:31 +02:00
|
|
|
|
_ -> lift Nothing
|
|
|
|
|
where
|
2020-08-28 08:32:21 +02:00
|
|
|
|
error' operationName = concat
|
|
|
|
|
[ "There can be only one operation named \""
|
|
|
|
|
, Text.unpack operationName
|
|
|
|
|
, "\"."
|
|
|
|
|
]
|
2020-08-27 09:04:31 +02:00
|
|
|
|
filterByName thisName definition' accumulator
|
|
|
|
|
| (viewOperation -> Just operationDefinition) <- definition'
|
|
|
|
|
, OperationDefinition _ (Just thatName) _ _ _ thatLocation <- operationDefinition
|
|
|
|
|
, thisName == thatName = thatLocation : accumulator
|
|
|
|
|
| otherwise = accumulator
|
|
|
|
|
|
2020-08-28 08:32:21 +02:00
|
|
|
|
findDuplicates :: (Definition -> [Location] -> [Location])
|
|
|
|
|
-> Location
|
|
|
|
|
-> String
|
|
|
|
|
-> RuleT m
|
|
|
|
|
findDuplicates filterByName thisLocation errorMessage = do
|
|
|
|
|
ast' <- asks ast
|
|
|
|
|
let locations' = foldr filterByName [] ast'
|
|
|
|
|
if length locations' > 1 && head locations' == thisLocation
|
|
|
|
|
then pure $ error' locations'
|
|
|
|
|
else lift Nothing
|
|
|
|
|
where
|
|
|
|
|
error' locations' = Error
|
|
|
|
|
{ message = errorMessage
|
|
|
|
|
, locations = locations'
|
|
|
|
|
, path = []
|
|
|
|
|
}
|
|
|
|
|
|
2020-08-27 09:04:31 +02:00
|
|
|
|
viewOperation :: Definition -> Maybe OperationDefinition
|
|
|
|
|
viewOperation definition
|
|
|
|
|
| ExecutableDefinition executableDefinition <- definition
|
|
|
|
|
, DefinitionOperation operationDefinition <- executableDefinition =
|
|
|
|
|
Just operationDefinition
|
|
|
|
|
viewOperation _ = Nothing
|
2020-08-28 08:32:21 +02:00
|
|
|
|
|
2020-08-31 11:06:27 +02:00
|
|
|
|
viewFragment :: Definition -> Maybe FragmentDefinition
|
|
|
|
|
viewFragment definition
|
|
|
|
|
| ExecutableDefinition executableDefinition <- definition
|
|
|
|
|
, DefinitionFragment fragmentDefinition <- executableDefinition =
|
|
|
|
|
Just fragmentDefinition
|
|
|
|
|
viewFragment _ = Nothing
|
|
|
|
|
|
2020-08-28 08:32:21 +02:00
|
|
|
|
-- | Fragment definitions are referenced in fragment spreads by name. To avoid
|
|
|
|
|
-- ambiguity, each fragment’s name must be unique within a document.
|
|
|
|
|
--
|
|
|
|
|
-- Inline fragments are not considered fragment definitions, and are unaffected
|
|
|
|
|
-- by this validation rule.
|
|
|
|
|
uniqueFragmentNamesRule :: forall m. Rule m
|
|
|
|
|
uniqueFragmentNamesRule = FragmentDefinitionRule $ \case
|
|
|
|
|
FragmentDefinition thisName _ _ _ thisLocation ->
|
|
|
|
|
findDuplicates (filterByName thisName) thisLocation (error' thisName)
|
|
|
|
|
where
|
|
|
|
|
error' fragmentName = concat
|
|
|
|
|
[ "There can be only one fragment named \""
|
|
|
|
|
, Text.unpack fragmentName
|
|
|
|
|
, "\"."
|
|
|
|
|
]
|
|
|
|
|
filterByName thisName definition accumulator
|
2020-08-31 11:06:27 +02:00
|
|
|
|
| Just fragmentDefinition <- viewFragment definition
|
2020-08-28 08:32:21 +02:00
|
|
|
|
, FragmentDefinition thatName _ _ _ thatLocation <- fragmentDefinition
|
|
|
|
|
, thisName == thatName = thatLocation : accumulator
|
|
|
|
|
| otherwise = accumulator
|
2020-08-31 11:06:27 +02:00
|
|
|
|
|
|
|
|
|
-- | Named fragment spreads must refer to fragments defined within the document.
|
|
|
|
|
-- It is a validation error if the target of a spread is not defined.
|
|
|
|
|
fragmentSpreadTargetDefinedRule :: forall m. Rule m
|
2020-09-07 22:01:49 +02:00
|
|
|
|
fragmentSpreadTargetDefinedRule = FragmentSpreadRule $ \case
|
2020-08-31 11:06:27 +02:00
|
|
|
|
FragmentSpread fragmentName _ location -> do
|
|
|
|
|
ast' <- asks ast
|
2020-09-04 19:12:19 +02:00
|
|
|
|
case find (isSpreadTarget fragmentName) ast' of
|
2020-08-31 11:06:27 +02:00
|
|
|
|
Nothing -> pure $ Error
|
|
|
|
|
{ message = error' fragmentName
|
|
|
|
|
, locations = [location]
|
|
|
|
|
, path = []
|
|
|
|
|
}
|
|
|
|
|
Just _ -> lift Nothing
|
|
|
|
|
where
|
|
|
|
|
error' fragmentName = concat
|
|
|
|
|
[ "Fragment target \""
|
|
|
|
|
, Text.unpack fragmentName
|
|
|
|
|
, "\" is undefined."
|
|
|
|
|
]
|
2020-09-04 19:12:19 +02:00
|
|
|
|
|
|
|
|
|
isSpreadTarget :: Text -> Definition -> Bool
|
|
|
|
|
isSpreadTarget thisName (viewFragment -> Just fragmentDefinition)
|
|
|
|
|
| FragmentDefinition thatName _ _ _ _ <- fragmentDefinition
|
|
|
|
|
, thisName == thatName = True
|
|
|
|
|
isSpreadTarget _ _ = False
|
|
|
|
|
|
|
|
|
|
-- | Fragments must be specified on types that exist in the schema. This applies
|
|
|
|
|
-- for both named and inline fragments. If they are not defined in the schema,
|
|
|
|
|
-- the query does not validate.
|
|
|
|
|
fragmentSpreadTypeExistenceRule :: forall m. Rule m
|
|
|
|
|
fragmentSpreadTypeExistenceRule = SelectionRule $ \case
|
2020-09-07 22:01:49 +02:00
|
|
|
|
FragmentSpreadSelection fragmentSelection
|
|
|
|
|
| FragmentSpread fragmentName _ location <- fragmentSelection -> do
|
|
|
|
|
ast' <- asks ast
|
|
|
|
|
target <- lift $ find (isSpreadTarget fragmentName) ast'
|
|
|
|
|
typeCondition <- extractTypeCondition target
|
|
|
|
|
types' <- asks types
|
|
|
|
|
case HashMap.lookup typeCondition types' of
|
|
|
|
|
Nothing -> pure $ Error
|
|
|
|
|
{ message = spreadError fragmentName typeCondition
|
|
|
|
|
, locations = [location]
|
|
|
|
|
, path = []
|
|
|
|
|
}
|
|
|
|
|
Just _ -> lift Nothing
|
|
|
|
|
InlineFragmentSelection fragmentSelection
|
|
|
|
|
| InlineFragment maybeType _ _ location <- fragmentSelection
|
|
|
|
|
, Just typeCondition <- maybeType -> do
|
|
|
|
|
types' <- asks types
|
|
|
|
|
case HashMap.lookup typeCondition types' of
|
|
|
|
|
Nothing -> pure $ Error
|
|
|
|
|
{ message = inlineError typeCondition
|
|
|
|
|
, locations = [location]
|
|
|
|
|
, path = []
|
|
|
|
|
}
|
|
|
|
|
Just _ -> lift Nothing
|
2020-09-04 19:12:19 +02:00
|
|
|
|
_ -> lift Nothing
|
|
|
|
|
where
|
|
|
|
|
extractTypeCondition (viewFragment -> Just fragmentDefinition) =
|
|
|
|
|
let FragmentDefinition _ typeCondition _ _ _ = fragmentDefinition
|
|
|
|
|
in pure typeCondition
|
|
|
|
|
extractTypeCondition _ = lift Nothing
|
2020-09-05 10:00:58 +02:00
|
|
|
|
spreadError fragmentName typeCondition = concat
|
2020-09-04 19:12:19 +02:00
|
|
|
|
[ "Fragment \""
|
|
|
|
|
, Text.unpack fragmentName
|
|
|
|
|
, "\" is specified on type \""
|
|
|
|
|
, Text.unpack typeCondition
|
|
|
|
|
, "\" which doesn't exist in the schema."
|
|
|
|
|
]
|
2020-09-05 10:00:58 +02:00
|
|
|
|
inlineError typeCondition = concat
|
|
|
|
|
[ "Inline fragment is specified on type \""
|
|
|
|
|
, Text.unpack typeCondition
|
|
|
|
|
, "\" which doesn't exist in the schema."
|
|
|
|
|
]
|
2020-09-07 22:01:49 +02:00
|
|
|
|
|
|
|
|
|
-- | Fragments can only be declared on unions, interfaces, and objects. They are
|
|
|
|
|
-- invalid on scalars. They can only be applied on non‐leaf fields. This rule
|
|
|
|
|
-- applies to both inline and named fragments.
|
|
|
|
|
fragmentsOnCompositeTypesRule :: forall m. Rule m
|
|
|
|
|
fragmentsOnCompositeTypesRule = FragmentRule definitionRule inlineRule
|
|
|
|
|
where
|
|
|
|
|
inlineRule (InlineFragment (Just typeCondition) _ _ location) =
|
|
|
|
|
check typeCondition location
|
|
|
|
|
inlineRule _ = lift Nothing
|
|
|
|
|
definitionRule (FragmentDefinition _ typeCondition _ _ location) =
|
|
|
|
|
check typeCondition location
|
|
|
|
|
check typeCondition location = do
|
|
|
|
|
types' <- asks types
|
|
|
|
|
-- Skip unknown types, they are checked by another rule.
|
|
|
|
|
_ <- lift $ HashMap.lookup typeCondition types'
|
|
|
|
|
case lookupTypeCondition typeCondition types' of
|
|
|
|
|
Nothing -> pure $ Error
|
|
|
|
|
{ message = errorMessage typeCondition
|
|
|
|
|
, locations = [location]
|
|
|
|
|
, path = []
|
|
|
|
|
}
|
|
|
|
|
Just _ -> lift Nothing
|
|
|
|
|
errorMessage typeCondition = concat
|
|
|
|
|
[ "Fragment cannot condition on non composite type \""
|
|
|
|
|
, Text.unpack typeCondition,
|
|
|
|
|
"\"."
|
|
|
|
|
]
|
2020-09-09 17:04:31 +02:00
|
|
|
|
|
|
|
|
|
-- | Defined fragments must be used within a document.
|
|
|
|
|
noUnusedFragmentsRule :: forall m. Rule m
|
|
|
|
|
noUnusedFragmentsRule = FragmentDefinitionRule $ \fragment ->
|
|
|
|
|
asks ast >>= findSpreadByName fragment
|
|
|
|
|
where
|
|
|
|
|
findSpreadByName (FragmentDefinition fragName _ _ _ location) definitions
|
|
|
|
|
| foldr (go fragName) False definitions = lift Nothing
|
|
|
|
|
| otherwise = pure $ Error
|
|
|
|
|
{ message = errorMessage fragName
|
|
|
|
|
, locations = [location]
|
|
|
|
|
, path = []
|
|
|
|
|
}
|
|
|
|
|
errorMessage fragName = concat
|
|
|
|
|
[ "Fragment \""
|
|
|
|
|
, Text.unpack fragName
|
|
|
|
|
, "\" is never used."
|
|
|
|
|
]
|
|
|
|
|
go fragName (viewOperation -> Just operation) accumulator
|
|
|
|
|
| SelectionSet selections _ <- operation =
|
|
|
|
|
evaluateSelections fragName accumulator selections
|
|
|
|
|
| OperationDefinition _ _ _ _ selections _ <- operation =
|
|
|
|
|
evaluateSelections fragName accumulator selections
|
|
|
|
|
go fragName (viewFragment -> Just fragment) accumulator
|
|
|
|
|
| FragmentDefinition _ _ _ selections _ <- fragment =
|
|
|
|
|
evaluateSelections fragName accumulator selections
|
|
|
|
|
go _ _ _ = False
|
|
|
|
|
evaluateSelection fragName selection accumulator
|
|
|
|
|
| FragmentSpreadSelection spreadSelection <- selection
|
|
|
|
|
, FragmentSpread spreadName _ _ <- spreadSelection
|
|
|
|
|
, spreadName == fragName = True
|
|
|
|
|
| FieldSelection fieldSelection <- selection
|
|
|
|
|
, Field _ _ _ _ selections _ <- fieldSelection =
|
|
|
|
|
evaluateSelections fragName accumulator selections
|
|
|
|
|
| InlineFragmentSelection inlineSelection <- selection
|
|
|
|
|
, InlineFragment _ _ selections _ <- inlineSelection =
|
|
|
|
|
evaluateSelections fragName accumulator selections
|
|
|
|
|
| otherwise = accumulator || False
|
|
|
|
|
evaluateSelections :: Foldable t => Name -> Bool -> t Selection -> Bool
|
|
|
|
|
evaluateSelections fragName accumulator selections =
|
|
|
|
|
foldr (evaluateSelection fragName) accumulator selections
|