graphql/tests/Language/GraphQL/ExecuteSpec.hs

418 lines
19 KiB
Haskell
Raw Normal View History

{- 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-06-10 11:42:00 +02:00
{-# LANGUAGE OverloadedStrings #-}
2020-09-11 08:03:49 +02:00
{-# LANGUAGE QuasiQuotes #-}
2022-01-04 12:40:41 +01:00
2020-06-10 11:42:00 +02:00
module Language.GraphQL.ExecuteSpec
( spec
) where
import Control.Exception (Exception(..), SomeException)
import Control.Monad.Catch (throwM)
import Data.Conduit
2020-06-10 11:42:00 +02:00
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Typeable (cast)
import Language.GraphQL.AST (Document, Location(..), Name)
2020-06-10 11:42:00 +02:00
import Language.GraphQL.AST.Parser (document)
import Language.GraphQL.Error
import Language.GraphQL.Execute (execute)
2021-09-22 08:50:20 +02:00
import Language.GraphQL.TH
import qualified Language.GraphQL.Type.Schema as Schema
2022-02-11 20:50:53 +01:00
import qualified Language.GraphQL.Type as Type
import Language.GraphQL.Type
import qualified Language.GraphQL.Type.In as In
import qualified Language.GraphQL.Type.Out as Out
import Prelude hiding (id)
import Test.Hspec (Spec, context, describe, it, shouldBe)
2020-06-10 11:42:00 +02:00
import Text.Megaparsec (parse)
2022-01-04 12:40:41 +01:00
import Schemas.HeroSchema (heroSchema)
import Data.Maybe (fromJust)
import qualified Data.Sequence as Seq
2022-02-11 20:50:53 +01:00
import qualified Data.Text as Text
2020-06-10 11:42:00 +02:00
data PhilosopherException = PhilosopherException
deriving Show
instance Exception PhilosopherException where
toException = toException. ResolverException
fromException e = do
ResolverException resolverException <- fromException e
cast resolverException
2020-09-28 07:06:15 +02:00
philosopherSchema :: Schema (Either SomeException)
philosopherSchema =
schemaWithTypes Nothing queryType Nothing subscriptionRoot extraTypes mempty
where
subscriptionRoot = Just subscriptionType
extraTypes =
[ Schema.ObjectType bookType
, Schema.ObjectType bookCollectionType
]
2020-06-10 11:42:00 +02:00
queryType :: Out.ObjectType (Either SomeException)
2020-06-10 11:42:00 +02:00
queryType = Out.ObjectType "Query" Nothing []
$ HashMap.fromList
[ ("philosopher", ValueResolver philosopherField philosopherResolver)
, ("genres", ValueResolver genresField genresResolver)
2021-09-03 22:47:49 +02:00
, ("count", ValueResolver countField countResolver)
]
2020-06-10 11:42:00 +02:00
where
philosopherField =
2021-09-03 22:47:49 +02:00
Out.Field Nothing (Out.NamedObjectType philosopherType)
$ HashMap.singleton "id"
$ In.Argument Nothing (In.NamedScalarType id) Nothing
philosopherResolver = pure $ Object mempty
genresField =
2021-09-03 22:47:49 +02:00
let fieldType = Out.ListType $ Out.NonNullScalarType string
in Out.Field Nothing fieldType HashMap.empty
genresResolver :: Resolve (Either SomeException)
genresResolver = throwM PhilosopherException
2021-09-03 22:47:49 +02:00
countField =
let fieldType = Out.NonNullScalarType int
in Out.Field Nothing fieldType HashMap.empty
countResolver = pure ""
2020-06-12 07:58:08 +02:00
musicType :: Out.ObjectType (Either SomeException)
musicType = Out.ObjectType "Music" Nothing []
$ HashMap.fromList resolvers
where
resolvers =
[ ("instrument", ValueResolver instrumentField instrumentResolver)
]
instrumentResolver = pure $ String "piano"
instrumentField = Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
poetryType :: Out.ObjectType (Either SomeException)
poetryType = Out.ObjectType "Poetry" Nothing []
$ HashMap.fromList resolvers
where
resolvers =
[ ("genre", ValueResolver genreField genreResolver)
]
genreResolver = pure $ String "Futurism"
genreField = Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
interestType :: Out.UnionType (Either SomeException)
interestType = Out.UnionType "Interest" Nothing [musicType, poetryType]
philosopherType :: Out.ObjectType (Either SomeException)
2020-06-12 07:58:08 +02:00
philosopherType = Out.ObjectType "Philosopher" Nothing []
$ HashMap.fromList resolvers
where
resolvers =
[ ("firstName", ValueResolver firstNameField firstNameResolver)
, ("lastName", ValueResolver lastNameField lastNameResolver)
, ("school", ValueResolver schoolField schoolResolver)
, ("interest", ValueResolver interestField interestResolver)
, ("majorWork", ValueResolver majorWorkField majorWorkResolver)
, ("century", ValueResolver centuryField centuryResolver)
2021-09-17 10:01:14 +02:00
, ("firstLanguage", ValueResolver firstLanguageField firstLanguageResolver)
2020-06-12 07:58:08 +02:00
]
firstNameField =
Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
firstNameResolver = pure $ String "Friedrich"
lastNameField
= Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
lastNameResolver = pure $ String "Nietzsche"
schoolField
= Out.Field Nothing (Out.NonNullEnumType schoolType) HashMap.empty
schoolResolver = pure $ Enum "EXISTENTIALISM"
interestField
= Out.Field Nothing (Out.NonNullUnionType interestType) HashMap.empty
interestResolver = pure
$ Object
$ HashMap.fromList [("instrument", "piano")]
majorWorkField
= Out.Field Nothing (Out.NonNullInterfaceType workType) HashMap.empty
majorWorkResolver = pure
$ Object
$ HashMap.fromList
[ ("title", "Also sprach Zarathustra: Ein Buch für Alle und Keinen")
]
centuryField =
Out.Field Nothing (Out.NonNullScalarType int) HashMap.empty
centuryResolver = pure $ Float 18.5
2021-09-17 10:01:14 +02:00
firstLanguageField
= Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
firstLanguageResolver = pure Null
workType :: Out.InterfaceType (Either SomeException)
workType = Out.InterfaceType "Work" Nothing []
$ HashMap.fromList fields
where
fields = [("title", titleField)]
titleField = Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
bookType :: Out.ObjectType (Either SomeException)
bookType = Out.ObjectType "Book" Nothing [workType]
$ HashMap.fromList resolvers
where
resolvers =
[ ("title", ValueResolver titleField titleResolver)
]
titleField = Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
titleResolver = pure "Also sprach Zarathustra: Ein Buch für Alle und Keinen"
bookCollectionType :: Out.ObjectType (Either SomeException)
bookCollectionType = Out.ObjectType "Book" Nothing [workType]
$ HashMap.fromList resolvers
where
resolvers =
[ ("title", ValueResolver titleField titleResolver)
]
titleField = Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
titleResolver = pure "The Three Critiques"
2020-06-10 11:42:00 +02:00
subscriptionType :: Out.ObjectType (Either SomeException)
subscriptionType = Out.ObjectType "Subscription" Nothing []
$ HashMap.singleton "newQuote"
$ EventStreamResolver quoteField (pure $ Object mempty)
$ pure $ yield $ Object mempty
where
quoteField =
Out.Field Nothing (Out.NonNullObjectType quoteType) HashMap.empty
quoteType :: Out.ObjectType (Either SomeException)
quoteType = Out.ObjectType "Quote" Nothing []
$ HashMap.singleton "quote"
$ ValueResolver quoteField
$ pure "Naturam expelles furca, tamen usque recurret."
where
quoteField =
Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
2022-02-11 20:50:53 +01:00
schoolType :: Type.EnumType
schoolType = EnumType "School" Nothing $ HashMap.fromList
[ ("NOMINALISM", EnumValue Nothing)
, ("REALISM", EnumValue Nothing)
, ("IDEALISM", EnumValue Nothing)
]
2020-09-11 08:03:49 +02:00
type EitherStreamOrValue = Either
2022-02-11 20:50:53 +01:00
(ResponseEventStream (Either SomeException) Type.Value)
(Response Type.Value)
2020-09-11 08:03:49 +02:00
execute' :: Document -> Either SomeException EitherStreamOrValue
2020-09-28 07:06:15 +02:00
execute' =
2022-02-11 20:50:53 +01:00
execute philosopherSchema Nothing (mempty :: HashMap Name Type.Value)
2020-09-11 08:03:49 +02:00
2020-06-10 11:42:00 +02:00
spec :: Spec
spec =
2020-06-12 07:58:08 +02:00
describe "execute" $ do
2020-09-11 08:03:49 +02:00
it "rejects recursive fragments" $
2021-09-22 08:50:20 +02:00
let sourceQuery = [gql|
2020-09-11 08:03:49 +02:00
{
...cyclicFragment
}
fragment cyclicFragment on Query {
...cyclicFragment
}
|]
2021-12-24 13:35:18 +01:00
expected = Response (Object mempty) mempty
2020-09-11 08:03:49 +02:00
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" sourceQuery
in actual `shouldBe` expected
context "Query" $ do
it "skips unknown fields" $
2021-12-24 13:35:18 +01:00
let data'' = Object
$ HashMap.singleton "philosopher"
$ Object
$ HashMap.singleton "firstName"
$ String "Friedrich"
expected = Response data'' mempty
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ philosopher { firstName surname } }"
in actual `shouldBe` expected
it "merges selections" $
2021-12-24 13:35:18 +01:00
let data'' = Object
$ HashMap.singleton "philosopher"
$ Object
$ HashMap.fromList
[ ("firstName", String "Friedrich")
, ("lastName", String "Nietzsche")
]
expected = Response data'' mempty
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ philosopher { firstName } philosopher { lastName } }"
in actual `shouldBe` expected
it "errors on invalid output enum values" $
2021-12-24 13:35:18 +01:00
let data'' = Object $ HashMap.singleton "philosopher" Null
executionErrors = pure $ Error
2021-09-01 08:51:20 +02:00
{ message =
"Value completion error. Expected type !School, found: EXISTENTIALISM."
, locations = [Location 1 17]
2021-09-01 08:51:20 +02:00
, path = [Segment "philosopher", Segment "school"]
}
expected = Response data'' executionErrors
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ philosopher { school } }"
in actual `shouldBe` expected
it "gives location information for non-null unions" $
2021-12-24 13:35:18 +01:00
let data'' = Object $ HashMap.singleton "philosopher" Null
executionErrors = pure $ Error
2021-09-01 08:51:20 +02:00
{ message =
"Value completion error. Expected type !Interest, found: { instrument: \"piano\" }."
, locations = [Location 1 17]
2021-09-01 08:51:20 +02:00
, path = [Segment "philosopher", Segment "interest"]
}
expected = Response data'' executionErrors
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ philosopher { interest } }"
in actual `shouldBe` expected
it "gives location information for invalid interfaces" $
2021-12-24 13:35:18 +01:00
let data'' = Object $ HashMap.singleton "philosopher" Null
executionErrors = pure $ Error
2021-09-01 08:51:20 +02:00
{ message
= "Value completion error. Expected type !Work, found:\
\ { title: \"Also sprach Zarathustra: Ein Buch f\252r Alle und Keinen\" }."
, locations = [Location 1 17]
2021-09-01 08:51:20 +02:00
, path = [Segment "philosopher", Segment "majorWork"]
}
expected = Response data'' executionErrors
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ philosopher { majorWork { title } } }"
in actual `shouldBe` expected
it "gives location information for invalid scalar arguments" $
2021-12-24 13:35:18 +01:00
let data'' = Object $ HashMap.singleton "philosopher" Null
executionErrors = pure $ Error
2021-09-02 08:45:23 +02:00
{ message =
"Argument \"id\" has invalid type. Expected type ID, found: True."
, locations = [Location 1 15]
2021-09-02 08:45:23 +02:00
, path = [Segment "philosopher"]
}
expected = Response data'' executionErrors
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ philosopher(id: true) { lastName } }"
in actual `shouldBe` expected
it "gives location information for failed result coercion" $
2021-12-24 13:35:18 +01:00
let data'' = Object $ HashMap.singleton "philosopher" Null
executionErrors = pure $ Error
2021-09-03 22:47:49 +02:00
{ message = "Unable to coerce result to !Int."
, locations = [Location 1 26]
2021-09-03 22:47:49 +02:00
, path = [Segment "philosopher", Segment "century"]
}
expected = Response data'' executionErrors
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ philosopher(id: \"1\") { century } }"
in actual `shouldBe` expected
it "gives location information for failed result coercion" $
2021-12-24 13:35:18 +01:00
let data'' = Object $ HashMap.singleton "genres" Null
executionErrors = pure $ Error
{ message = "PhilosopherException"
, locations = [Location 1 3]
2021-09-03 22:47:49 +02:00
, path = [Segment "genres"]
}
expected = Response data'' executionErrors
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ genres }"
in actual `shouldBe` expected
2021-09-03 22:47:49 +02:00
it "sets data to null if a root field isn't nullable" $
let executionErrors = pure $ Error
{ message = "Unable to coerce result to !Int."
, locations = [Location 1 3]
, path = [Segment "count"]
}
2021-12-24 13:35:18 +01:00
expected = Response Null executionErrors
2021-09-03 22:47:49 +02:00
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ count }"
in actual `shouldBe` expected
2021-09-17 10:01:14 +02:00
it "detects nullability errors" $
2021-12-24 13:35:18 +01:00
let data'' = Object $ HashMap.singleton "philosopher" Null
2021-09-17 10:01:14 +02:00
executionErrors = pure $ Error
{ message = "Value completion error. Expected type !String, found: null."
, locations = [Location 1 26]
, path = [Segment "philosopher", Segment "firstLanguage"]
}
expected = Response data'' executionErrors
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ philosopher(id: \"1\") { firstLanguage } }"
in actual `shouldBe` expected
2022-02-11 20:50:53 +01:00
context "queryError" $ do
let
namedQuery name = "query " <> name <> " { philosopher(id: \"1\") { interest } }"
twoQueries = namedQuery "A" <> " " <> namedQuery "B"
startsWith :: Text.Text -> Text.Text -> Bool
startsWith xs ys = Text.take (Text.length ys) xs == ys
it "throws operation name is required error" $
let expectedErrorMessage :: Text.Text
expectedErrorMessage = "Operation name is required"
Right (Right (Response _ executionErrors)) = either (pure . parseError) execute' $ parse document "" twoQueries
Error msg _ _ = Seq.index executionErrors 0
in msg `startsWith` expectedErrorMessage `shouldBe` True
it "throws operation not found error" $
let expectedErrorMessage :: Text.Text
expectedErrorMessage = "Operation \"C\" is not found"
execute'' :: Document -> Either SomeException EitherStreamOrValue
execute'' = execute philosopherSchema (Just "C") (mempty :: HashMap Name Type.Value)
Right (Right (Response _ executionErrors)) = either (pure . parseError) execute''
$ parse document "" twoQueries
Error msg _ _ = Seq.index executionErrors 0
in msg `startsWith` expectedErrorMessage `shouldBe` True
it "throws variable coercion error" $
let data'' = Null
executionErrors = pure $ Error
{ message = "Failed to coerce the variable $id: String."
, locations =[Location 1 7]
, path = []
}
expected = Response data'' executionErrors
executeWithVars :: Document -> Either SomeException EitherStreamOrValue
executeWithVars = execute philosopherSchema Nothing (HashMap.singleton "id" (Type.Int 1))
Right (Right actual) = either (pure . parseError) executeWithVars
$ parse document "" "query($id: String) { philosopher(id: \"1\") { firstLanguage } }"
in actual `shouldBe` expected
it "throws variable unkown input type error" $
let data'' = Null
executionErrors = pure $ Error
{ message = "Variable $id has unknown type Cat."
, locations =[Location 1 7]
, path = []
}
expected = Response data'' executionErrors
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "query($id: Cat) { philosopher(id: \"1\") { firstLanguage } }"
in actual `shouldBe` expected
2022-01-04 12:40:41 +01:00
context "Error path" $ do
let executeHero :: Document -> Either SomeException EitherStreamOrValue
2022-02-11 20:50:53 +01:00
executeHero = execute heroSchema Nothing (HashMap.empty :: HashMap Name Type.Value)
2022-01-04 12:40:41 +01:00
it "at the beggining of the list" $
let Right (Right actual) = either (pure . parseError) executeHero
$ parse document "" "{ hero(id: \"1\") { friends { name } } }"
Response _ errors' = actual
Error _ _ path' = fromJust $ Seq.lookup 0 errors'
expected = [Segment "hero", Segment "friends", Index 0, Segment "name"]
in path' `shouldBe` expected
context "Subscription" $
it "subscribes" $
2021-12-24 13:35:18 +01:00
let data'' = Object
$ HashMap.singleton "newQuote"
$ Object
$ HashMap.singleton "quote"
$ String "Naturam expelles furca, tamen usque recurret."
expected = Response data'' mempty
Right (Left stream) = either (pure . parseError) execute'
$ parse document "" "subscription { newQuote { quote } }"
Right (Just actual) = runConduit $ stream .| await
in actual `shouldBe` expected