Define resolvers on type fields

Returning resolvers from other resolvers isn't supported anymore. Since
we have a type system now, we define the resolvers in the object type
fields and pass an object with the previous result to them.
This commit is contained in:
2020-05-27 23:18:35 +02:00
parent c06d0b8e95
commit d12577ae71
25 changed files with 534 additions and 516 deletions

View File

@ -11,9 +11,8 @@ import qualified Data.HashMap.Strict as HashMap
import Data.Maybe (isNothing)
import Data.Scientific (scientific)
import qualified Data.Set as Set
import Language.GraphQL.AST.Core
import Language.GraphQL.AST.Document (Name)
import Language.GraphQL.Execute.Coerce
import Language.GraphQL.Schema
import Language.GraphQL.Type.Definition
import qualified Language.GraphQL.Type.In as In
import Prelude hiding (id)
@ -23,12 +22,12 @@ direction :: EnumType
direction = EnumType "Direction" Nothing
$ Set.fromList ["NORTH", "EAST", "SOUTH", "WEST"]
coerceInputLiteral :: In.Type -> In.Value -> Maybe Subs
coerceInputLiteral :: In.Type -> Value -> Maybe Subs
coerceInputLiteral input value = coerceInputLiterals
(HashMap.singleton "variableName" input)
(HashMap.singleton "variableName" value)
lookupActual :: Maybe (HashMap Name In.Value) -> Maybe In.Value
lookupActual :: Maybe (HashMap Name Value) -> Maybe Value
lookupActual = (HashMap.lookup "variableName" =<<)
singletonInputObject :: In.Type
@ -42,22 +41,22 @@ spec :: Spec
spec = do
describe "ToGraphQL Aeson" $ do
it "coerces strings" $
let expected = Just (In.String "asdf")
let expected = Just (String "asdf")
actual = coerceVariableValue
(In.NamedScalarType string) (Aeson.String "asdf")
in actual `shouldBe` expected
it "coerces non-null strings" $
let expected = Just (In.String "asdf")
let expected = Just (String "asdf")
actual = coerceVariableValue
(In.NonNullScalarType string) (Aeson.String "asdf")
in actual `shouldBe` expected
it "coerces booleans" $
let expected = Just (In.Boolean True)
let expected = Just (Boolean True)
actual = coerceVariableValue
(In.NamedScalarType boolean) (Aeson.Bool True)
in actual `shouldBe` expected
it "coerces zero to an integer" $
let expected = Just (In.Int 0)
let expected = Just (Int 0)
actual = coerceVariableValue
(In.NamedScalarType int) (Aeson.Number 0)
in actual `shouldBe` expected
@ -66,24 +65,24 @@ spec = do
(In.NamedScalarType int) (Aeson.Number $ scientific 14 (-1))
in actual `shouldSatisfy` isNothing
it "coerces float numbers" $
let expected = Just (In.Float 1.4)
let expected = Just (Float 1.4)
actual = coerceVariableValue
(In.NamedScalarType float) (Aeson.Number $ scientific 14 (-1))
in actual `shouldBe` expected
it "coerces IDs" $
let expected = Just (In.String "1234")
let expected = Just (String "1234")
actual = coerceVariableValue
(In.NamedScalarType id) (Aeson.String "1234")
in actual `shouldBe` expected
it "coerces input objects" $
let actual = coerceVariableValue singletonInputObject
$ Aeson.object ["field" .= ("asdf" :: Aeson.Value)]
expected = Just $ In.Object $ HashMap.singleton "field" "asdf"
expected = Just $ Object $ HashMap.singleton "field" "asdf"
in actual `shouldBe` expected
it "skips the field if it is missing in the variables" $
let actual = coerceVariableValue
singletonInputObject Aeson.emptyObject
expected = Just $ In.Object HashMap.empty
expected = Just $ Object HashMap.empty
in actual `shouldBe` expected
it "fails if input object value contains extra fields" $
let actual = coerceVariableValue singletonInputObject
@ -95,25 +94,25 @@ spec = do
in actual `shouldSatisfy` isNothing
it "preserves null" $
let actual = coerceVariableValue (In.NamedScalarType id) Aeson.Null
in actual `shouldBe` Just In.Null
in actual `shouldBe` Just Null
it "preserves list order" $
let list = Aeson.toJSONList ["asdf" :: Aeson.Value, "qwer"]
listType = (In.ListType $ In.NamedScalarType string)
actual = coerceVariableValue listType list
expected = Just $ In.List [In.String "asdf", In.String "qwer"]
expected = Just $ List [String "asdf", String "qwer"]
in actual `shouldBe` expected
describe "coerceInputLiterals" $ do
it "coerces enums" $
let expected = Just (In.Enum "NORTH")
let expected = Just (Enum "NORTH")
actual = coerceInputLiteral
(In.NamedEnumType direction) (In.Enum "NORTH")
(In.NamedEnumType direction) (Enum "NORTH")
in lookupActual actual `shouldBe` expected
it "fails with non-existing enum value" $
let actual = coerceInputLiteral
(In.NamedEnumType direction) (In.Enum "NORTH_EAST")
(In.NamedEnumType direction) (Enum "NORTH_EAST")
in actual `shouldSatisfy` isNothing
it "coerces integers to IDs" $
let expected = Just (In.String "1234")
actual = coerceInputLiteral (In.NamedScalarType id) (In.Int 1234)
let expected = Just (String "1234")
actual = coerceInputLiteral (In.NamedScalarType id) (Int 1234)
in lookupActual actual `shouldBe` expected

View File

@ -1,32 +0,0 @@
{-# LANGUAGE OverloadedStrings #-}
module Language.GraphQL.SchemaSpec
( spec
) where
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Types as Aeson
import qualified Data.HashMap.Strict as HashMap
import qualified Data.Sequence as Sequence
import Language.GraphQL.AST.Core
import Language.GraphQL.Error
import Language.GraphQL.Schema
import qualified Language.GraphQL.Type.Out as Out
import Test.Hspec (Spec, describe, it, shouldBe)
spec :: Spec
spec =
describe "resolve" $
it "ignores invalid __typename" $ do
let resolver = pure $ object
[ Resolver "field" $ pure $ Out.String "T"
]
schema = HashMap.singleton "__typename" resolver
fields = Sequence.singleton
$ SelectionFragment
$ Fragment "T" Sequence.empty
expected = Aeson.object
[ ("data" , Aeson.emptyObject)
]
actual <- runCollectErrs (resolve schema fields)
actual `shouldBe` expected

View File

@ -3,13 +3,12 @@ module Language.GraphQL.Type.OutSpec
( spec
) where
import Data.Functor.Identity (Identity)
import qualified Language.GraphQL.Type.Out as Out
import Language.GraphQL.Type.Definition
import Test.Hspec (Spec, describe, it, shouldBe)
spec :: Spec
spec =
describe "Value" $
it "supports overloaded strings" $
let string = "Goldstaub abblasen." :: (Out.Value Identity)
in string `shouldBe` Out.String "Goldstaub abblasen."
let nietzsche = "Goldstaub abblasen." :: Value
in nietzsche `shouldBe` String "Goldstaub abblasen."