mirror of
https://github.com/hasura/graphql-engine.git
synced 2024-12-13 19:33:55 +03:00
server: give stack traces when encountering conflicting type definitions (#150)
Since PDV, introspection queries are parsed by a certain kind of reflection where during the GraphQL schema generation, we collect all GraphQL types used during schema generation to generate answers to introspection queries. This has a great advantage, namely that we don't need to keep track of which types are being used in our schema, as this information is extracted after the fact. But what happens when we encounter two types with the same name in the GraphQL schema? Well, they better be the same, otherwise we likely made a programming error. So what do we do when we *do* encounter a conflict? So far, we've been throwing a rather generic error message, namely `found conflicting definitions for <typename> when collecting types from the schema`. It does not specify what the conflict is, or how it arose. In fact, I'm a little bit hesitant to output more information about what the conflict is, because we support many different kinds of GraphQL types, and these can have disagreements in many different ways. It'd be a bit tiring (not to mention error-prone) to spell this out explicitly for all types. And, in any case, at the moment our equality checks for types is incorrect anyway, as we are avoiding implementing a certain recursive equality checking algorithm. As it turns out, type conflicts arise not just due to programming errors, but also arise naturally under certain configurations. @codingkarthik encountered an interesting case recently where adding a specific remote and a single unrelated database table would result in a conflict in our Relay schema. It was not readily visible how this conflict arose: this took significant engineering effort. This adds stack traces to type collection, so that we can inform the user where the type conflict is taking place. The origin of the above conflict can easily be spotted using this PR. Here's a sample error message: ``` Found conflicting definitions for "PageInfo". The definition at "mutation_root.UpdateUser.favourites.anime.edges.node.characters.pageInfo" differs from the the definition at "query_root.test_connection.pageInfo" ``` Co-authored-by: Antoine Leblanc <antoine@hasura.io> GitOrigin-RevId: d4c01c243022d8570b3c057b168a61c3033244ff
This commit is contained in:
parent
237ac68047
commit
be7f34891c
@ -54,6 +54,7 @@ This release contains the [PDV refactor (#4111)](https://github.com/hasura/graph
|
||||
|
||||
(Add entries here in the order of: server, console, cli, docs, others)
|
||||
|
||||
- server: output stack traces when encountering conflicting GraphQL types in the schema
|
||||
- server: add `--websocket-compression` command-line flag for enabling websocket compression (fix #3292)
|
||||
- server: some mutations that cannot be performed will no longer be in the schema (for instance, `delete_by_pk` mutations won't be shown to users that do not have select permissions on all primary keys) (#4111)
|
||||
- server: treat the absence of `backend_only` configuration and `backend_only: false` equally (closing #5059) (#4111)
|
||||
|
@ -55,11 +55,14 @@ import Hasura.Prelude
|
||||
import qualified Data.Aeson as J
|
||||
import qualified Data.HashMap.Strict.Extended as Map
|
||||
import qualified Data.HashSet as Set
|
||||
import Data.Hashable ( Hashable (..) )
|
||||
import qualified Data.List.NonEmpty as NE
|
||||
import qualified Data.Text as T
|
||||
|
||||
import Data.Text.Extended
|
||||
import Control.Lens.Extended
|
||||
import Control.Monad.Unique
|
||||
import Data.Functor.Classes
|
||||
import Data.Hashable ( Hashable (..) )
|
||||
import Language.GraphQL.Draft.Syntax ( Description (..), Name (..)
|
||||
, Value (..), Nullability(..)
|
||||
, GType (..), DirectiveLocation(..)
|
||||
@ -716,11 +719,33 @@ data Schema = Schema
|
||||
-- | Recursively collects all type definitions accessible from the given value.
|
||||
collectTypeDefinitions
|
||||
:: (HasTypeDefinitions a, MonadError ConflictingDefinitions m)
|
||||
=> a -> m (HashMap Name (Definition SomeTypeInfo))
|
||||
collectTypeDefinitions = flip execStateT Map.empty . accumulateTypeDefinitions
|
||||
=> a
|
||||
-> m (HashMap Name (Definition SomeTypeInfo))
|
||||
collectTypeDefinitions x =
|
||||
fmap (fmap fst) $
|
||||
flip execStateT Map.empty $
|
||||
flip runReaderT (TypeOriginStack []) $
|
||||
accumulateTypeDefinitions x
|
||||
|
||||
newtype TypeOriginStack = TypeOriginStack [Name]
|
||||
|
||||
-- Add the current field name to the origin stack
|
||||
typeOriginRecurse :: Name -> TypeOriginStack -> TypeOriginStack
|
||||
typeOriginRecurse field (TypeOriginStack origins) = TypeOriginStack (field:origins)
|
||||
|
||||
-- This is kind of a hack to make sure that the query root name is part of the origin stack
|
||||
typeRootRecurse :: Name -> TypeOriginStack -> TypeOriginStack
|
||||
typeRootRecurse rootName (TypeOriginStack []) = (TypeOriginStack [rootName])
|
||||
typeRootRecurse _ x = x
|
||||
|
||||
instance ToTxt TypeOriginStack where
|
||||
toTxt (TypeOriginStack fields) = T.intercalate "." $ toTxt <$> reverse fields
|
||||
|
||||
data ConflictingDefinitions
|
||||
= ConflictingDefinitions (Definition SomeTypeInfo) (Definition SomeTypeInfo)
|
||||
= ConflictingDefinitions
|
||||
(Definition SomeTypeInfo, TypeOriginStack)
|
||||
(Definition SomeTypeInfo, NonEmpty TypeOriginStack)
|
||||
-- ^ Type collection has found at least two types with the same name.
|
||||
|
||||
class HasTypeDefinitions a where
|
||||
-- | Recursively accumulates all type definitions accessible from the given
|
||||
@ -728,7 +753,9 @@ class HasTypeDefinitions a where
|
||||
-- recursive type definitions; see Note [Tying the knot] in Hasura.GraphQL.Parser.Class.
|
||||
accumulateTypeDefinitions
|
||||
:: ( MonadError ConflictingDefinitions m
|
||||
, MonadState (HashMap Name (Definition SomeTypeInfo)) m )
|
||||
, MonadReader TypeOriginStack m
|
||||
, MonadState (HashMap Name (Definition SomeTypeInfo, NonEmpty TypeOriginStack)) m
|
||||
)
|
||||
=> a -> m ()
|
||||
|
||||
instance HasTypeDefinitions (Definition (TypeInfo k)) where
|
||||
@ -736,18 +763,19 @@ instance HasTypeDefinitions (Definition (TypeInfo k)) where
|
||||
-- This is the important case! We actually have a type definition, so we
|
||||
-- need to add it to the state.
|
||||
definitions <- get
|
||||
stack <- ask
|
||||
let new = SomeTypeInfo <$> definition
|
||||
case Map.lookup (dName new) definitions of
|
||||
Nothing -> do
|
||||
put $! Map.insert (dName new) new definitions
|
||||
put $! Map.insert (dName new) (new, pure stack) definitions
|
||||
-- This type definition might reference other type definitions, so we
|
||||
-- still need to recur.
|
||||
accumulateTypeDefinitions (dInfo definition)
|
||||
Just old
|
||||
local (typeRootRecurse (getName definition)) $ accumulateTypeDefinitions (dInfo definition)
|
||||
Just (old, origins)
|
||||
-- It’s important we /don’t/ recur if we’ve already seen this definition
|
||||
-- before to avoid infinite loops; see Note [Tying the knot] in Hasura.GraphQL.Parser.Class.
|
||||
| old == new -> pure ()
|
||||
| otherwise -> throwError $ ConflictingDefinitions old new
|
||||
| old == new -> put $! Map.insert (dName new) (old, stack `NE.cons` origins) definitions
|
||||
| otherwise -> throwError $ ConflictingDefinitions (new, stack) (old, origins)
|
||||
|
||||
instance HasTypeDefinitions a => HasTypeDefinitions [a] where
|
||||
accumulateTypeDefinitions = traverse_ accumulateTypeDefinitions
|
||||
@ -778,7 +806,8 @@ instance HasTypeDefinitions (Definition InputObjectInfo) where
|
||||
accumulateTypeDefinitions = accumulateTypeDefinitions . fmap TIInputObject
|
||||
|
||||
instance HasTypeDefinitions (Definition InputFieldInfo) where
|
||||
accumulateTypeDefinitions = accumulateTypeDefinitions . dInfo
|
||||
accumulateTypeDefinitions Definition{..} =
|
||||
local (typeOriginRecurse dName) $ accumulateTypeDefinitions dInfo
|
||||
|
||||
instance HasTypeDefinitions InputFieldInfo where
|
||||
accumulateTypeDefinitions = \case
|
||||
@ -786,7 +815,8 @@ instance HasTypeDefinitions InputFieldInfo where
|
||||
IFOptional t _ -> accumulateTypeDefinitions t
|
||||
|
||||
instance HasTypeDefinitions (Definition FieldInfo) where
|
||||
accumulateTypeDefinitions = accumulateTypeDefinitions . dInfo
|
||||
accumulateTypeDefinitions Definition{..} =
|
||||
local (typeOriginRecurse dName) $ accumulateTypeDefinitions dInfo
|
||||
|
||||
instance HasTypeDefinitions FieldInfo where
|
||||
accumulateTypeDefinitions (FieldInfo args t) = do
|
||||
@ -794,10 +824,13 @@ instance HasTypeDefinitions FieldInfo where
|
||||
accumulateTypeDefinitions t
|
||||
|
||||
instance HasTypeDefinitions (Definition ObjectInfo) where
|
||||
accumulateTypeDefinitions = accumulateTypeDefinitions . fmap TIObject
|
||||
accumulateTypeDefinitions d@Definition{..} =
|
||||
local (typeOriginRecurse dName) $ accumulateTypeDefinitions (fmap TIObject d)
|
||||
|
||||
instance HasTypeDefinitions (Definition InterfaceInfo) where
|
||||
accumulateTypeDefinitions = accumulateTypeDefinitions . fmap TIInterface
|
||||
accumulateTypeDefinitions d@Definition{..} =
|
||||
local (typeOriginRecurse dName) $ accumulateTypeDefinitions (fmap TIInterface d)
|
||||
|
||||
instance HasTypeDefinitions (Definition UnionInfo) where
|
||||
accumulateTypeDefinitions = accumulateTypeDefinitions . fmap TIUnion
|
||||
accumulateTypeDefinitions d@Definition{..} =
|
||||
local (typeOriginRecurse dName) $ accumulateTypeDefinitions (fmap TIUnion d)
|
||||
|
@ -500,9 +500,9 @@ collectTypes
|
||||
=> a
|
||||
-> m (HashMap G.Name (P.Definition P.SomeTypeInfo))
|
||||
collectTypes x = case P.collectTypeDefinitions x of
|
||||
Left (P.ConflictingDefinitions type1 _) -> throw500 $
|
||||
"found conflicting definitions for " <> P.getName type1
|
||||
<<> " when collecting types from the schema"
|
||||
Left (P.ConflictingDefinitions (type1, origin1) (_type2, origins)) -> throw500 $
|
||||
"Found conflicting definitions for " <> P.getName type1
|
||||
<<> ". The definition at " <> origin1 <<> " differs from the the definition at " <>> commaSeparated origins
|
||||
Right tps -> pure tps
|
||||
|
||||
queryWithIntrospectionHelper
|
||||
|
Loading…
Reference in New Issue
Block a user