Provide an internal function to add errors

The old function, addErrMsg, takes only a string with an error
description, but more information is required for the execution errors:
locations and path. addErrMsg should be deprecated after the switching
to the new addError.
This commit is contained in:
Eugen Wissner 2021-05-09 12:34:39 +02:00
parent 5a5f265fe4
commit 0d23df3da2
Signed by: belka
GPG Key ID: A27FDC1E8EE902C0
4 changed files with 57 additions and 2 deletions

View File

@ -47,6 +47,7 @@ library
Test.Hspec.GraphQL Test.Hspec.GraphQL
other-modules: other-modules:
Language.GraphQL.Execute.Execution Language.GraphQL.Execute.Execution
Language.GraphQL.Execute.Internal
Language.GraphQL.Execute.Subscribe Language.GraphQL.Execute.Subscribe
Language.GraphQL.Execute.Transform Language.GraphQL.Execute.Transform
Language.GraphQL.Type.Definition Language.GraphQL.Type.Definition

View File

@ -21,6 +21,7 @@ import qualified Data.Text as Text
import Language.GraphQL.AST (Name) import Language.GraphQL.AST (Name)
import Language.GraphQL.Error import Language.GraphQL.Error
import Language.GraphQL.Execute.Coerce import Language.GraphQL.Execute.Coerce
import Language.GraphQL.Execute.Internal
import Language.GraphQL.Execute.OrderedMap (OrderedMap) import Language.GraphQL.Execute.OrderedMap (OrderedMap)
import qualified Language.GraphQL.Execute.OrderedMap as OrderedMap import qualified Language.GraphQL.Execute.OrderedMap as OrderedMap
import qualified Language.GraphQL.Execute.Transform as Transform import qualified Language.GraphQL.Execute.Transform as Transform
@ -123,7 +124,7 @@ completeValue outputType@(Out.EnumBaseType enumType) _ (Type.Enum enum) =
let Type.EnumType _ _ enumMembers = enumType let Type.EnumType _ _ enumMembers = enumType
in if HashMap.member enum enumMembers in if HashMap.member enum enumMembers
then coerceResult outputType $ Enum enum then coerceResult outputType $ Enum enum
else addErrMsg "Enum value completion failed." else addError $ Error "Enum value completion failed." [] []
completeValue (Out.ObjectBaseType objectType) fields result = completeValue (Out.ObjectBaseType objectType) fields result =
executeSelectionSet result objectType $ mergeSelectionSets fields executeSelectionSet result objectType $ mergeSelectionSets fields
completeValue (Out.InterfaceBaseType interfaceType) fields result completeValue (Out.InterfaceBaseType interfaceType) fields result

View File

@ -0,0 +1,25 @@
{- 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/. -}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE NamedFieldPuns #-}
module Language.GraphQL.Execute.Internal
( addError
) where
import Control.Monad.Trans.State (modify)
import Control.Monad.Catch (MonadCatch)
import Data.Sequence ((|>))
import Language.GraphQL.Error
import Language.GraphQL.Execute.Coerce
import Prelude hiding (null)
addError :: (Serialize a, MonadCatch m) => Error -> CollectErrsT m a
addError error' = modify appender >> pure null
where
appender :: Resolution m -> Resolution m
appender resolution@Resolution{ errors } = resolution
{ errors = errors |> error'
}

View File

@ -44,6 +44,7 @@ philosopherType = Out.ObjectType "Philosopher" Nothing []
resolvers = resolvers =
[ ("firstName", ValueResolver firstNameField firstNameResolver) [ ("firstName", ValueResolver firstNameField firstNameResolver)
, ("lastName", ValueResolver lastNameField lastNameResolver) , ("lastName", ValueResolver lastNameField lastNameResolver)
, ("school", ValueResolver schoolField schoolResolver)
] ]
firstNameField = firstNameField =
Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
@ -51,6 +52,9 @@ philosopherType = Out.ObjectType "Philosopher" Nothing []
lastNameField lastNameField
= Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty = Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
lastNameResolver = pure $ Type.String "Nietzsche" lastNameResolver = pure $ Type.String "Nietzsche"
schoolField
= Out.Field Nothing (Out.NonNullEnumType schoolType) HashMap.empty
schoolResolver = pure $ Type.Enum "EXISTENTIALISM"
subscriptionType :: Out.ObjectType (Either SomeException) subscriptionType :: Out.ObjectType (Either SomeException)
subscriptionType = Out.ObjectType "Subscription" Nothing [] subscriptionType = Out.ObjectType "Subscription" Nothing []
@ -70,6 +74,13 @@ quoteType = Out.ObjectType "Quote" Nothing []
quoteField = quoteField =
Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
schoolType :: EnumType
schoolType = EnumType "School" Nothing $ HashMap.fromList
[ ("NOMINALISM", EnumValue Nothing)
, ("REALISM", EnumValue Nothing)
, ("IDEALISM", EnumValue Nothing)
]
type EitherStreamOrValue = Either type EitherStreamOrValue = Either
(ResponseEventStream (Either SomeException) Aeson.Value) (ResponseEventStream (Either SomeException) Aeson.Value)
(Response Aeson.Value) (Response Aeson.Value)
@ -118,6 +129,23 @@ spec =
Right (Right actual) = either (pure . parseError) execute' Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ philosopher { firstName } philosopher { lastName } }" $ parse document "" "{ philosopher { firstName } philosopher { lastName } }"
in actual `shouldBe` expected in actual `shouldBe` expected
it "errors on invalid output enum values" $
let data'' = Aeson.object
[ "philosopher" .= Aeson.object
[ "school" .= Aeson.Null
]
]
executionErrors = pure $ Error
{ message = "Enum value completion failed."
, locations = []
, path = []
}
expected = Response data'' executionErrors
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ philosopher { school } }"
in actual `shouldBe` expected
context "Subscription" $ context "Subscription" $
it "subscribes" $ it "subscribes" $
let data'' = Aeson.object let data'' = Aeson.object