Add functional tests calling the graphql function
This commit is contained in:
@ -85,6 +85,7 @@ test-suite graphql-test
|
|||||||
Language.GraphQL.Execute.CoerceSpec
|
Language.GraphQL.Execute.CoerceSpec
|
||||||
Language.GraphQL.Execute.OrderedMapSpec
|
Language.GraphQL.Execute.OrderedMapSpec
|
||||||
Language.GraphQL.ExecuteSpec
|
Language.GraphQL.ExecuteSpec
|
||||||
|
Language.GraphQLSpec
|
||||||
Language.GraphQL.Type.OutSpec
|
Language.GraphQL.Type.OutSpec
|
||||||
Language.GraphQL.Validate.RulesSpec
|
Language.GraphQL.Validate.RulesSpec
|
||||||
Schemas.HeroSchema
|
Schemas.HeroSchema
|
||||||
@ -106,4 +107,6 @@ test-suite graphql-test
|
|||||||
unordered-containers,
|
unordered-containers,
|
||||||
containers,
|
containers,
|
||||||
vector
|
vector
|
||||||
|
build-tool-depends:
|
||||||
|
hspec-discover:hspec-discover
|
||||||
default-language: Haskell2010
|
default-language: Haskell2010
|
||||||
|
72
tests/Language/GraphQLSpec.hs
Normal file
72
tests/Language/GraphQLSpec.hs
Normal file
@ -0,0 +1,72 @@
|
|||||||
|
{- 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 OverloadedStrings #-}
|
||||||
|
|
||||||
|
module Language.GraphQLSpec
|
||||||
|
( spec
|
||||||
|
) where
|
||||||
|
|
||||||
|
import Data.HashMap.Strict (HashMap)
|
||||||
|
import qualified Data.HashMap.Strict as HashMap
|
||||||
|
import Language.GraphQL.AST (Name)
|
||||||
|
import Language.GraphQL.Error
|
||||||
|
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, describe, it, shouldBe)
|
||||||
|
import qualified Data.Text as Text
|
||||||
|
import Test.Hspec.Expectations
|
||||||
|
( Expectation
|
||||||
|
, expectationFailure
|
||||||
|
)
|
||||||
|
import Language.GraphQL (graphql)
|
||||||
|
|
||||||
|
queryType :: Out.ObjectType IO
|
||||||
|
queryType = Out.ObjectType "Query" Nothing []
|
||||||
|
$ HashMap.fromList
|
||||||
|
[ ("sequence", ValueResolver sequenceField sequenceResolver)
|
||||||
|
]
|
||||||
|
where
|
||||||
|
sequenceField =
|
||||||
|
let fieldType = Out.ListType $ Out.NonNullScalarType int
|
||||||
|
in Out.Field Nothing fieldType $ HashMap.fromList
|
||||||
|
[("values", In.Argument Nothing (In.NonNullListType $ In.NonNullScalarType int) Nothing)]
|
||||||
|
sequenceResolver = argument "values"
|
||||||
|
|
||||||
|
testSchema :: Schema IO
|
||||||
|
testSchema =
|
||||||
|
schemaWithTypes Nothing queryType Nothing Nothing mempty mempty
|
||||||
|
|
||||||
|
shouldResolveTo :: Text.Text -> HashMap Name Type.Value -> Response Type.Value -> Expectation
|
||||||
|
shouldResolveTo querySource variables expected = do
|
||||||
|
response <- graphql testSchema Nothing variables querySource
|
||||||
|
case response of
|
||||||
|
(Right result) -> result `shouldBe` expected
|
||||||
|
Left _ -> expectationFailure
|
||||||
|
"the query is expected to resolve to a value, but it resolved to an event stream"
|
||||||
|
|
||||||
|
spec :: Spec
|
||||||
|
spec =
|
||||||
|
describe "value to singleton list coercion" $ do
|
||||||
|
it "coerces a value to a singleton list" $
|
||||||
|
let data'' = Object $ HashMap.singleton "sequence" $ Type.List [Type.Int 5]
|
||||||
|
expected = Response data'' mempty
|
||||||
|
sourceQuery = "{ sequence(values: 5) }"
|
||||||
|
in shouldResolveTo sourceQuery HashMap.empty expected
|
||||||
|
|
||||||
|
it "coerces a variable to a singleton list" $
|
||||||
|
let variables = HashMap.singleton "values" $ Type.Int 5
|
||||||
|
data'' = Object $ HashMap.singleton "sequence" $ Type.List [Type.Int 5]
|
||||||
|
expected = Response data'' mempty
|
||||||
|
sourceQuery = "query($values: [Int!]!) { sequence(values: $values) }"
|
||||||
|
in shouldResolveTo sourceQuery variables expected
|
||||||
|
|
||||||
|
it "accepts a singleton list" $
|
||||||
|
let data'' = Object $ HashMap.singleton "sequence" $ Type.List [Type.Int 5]
|
||||||
|
expected = Response data'' mempty
|
||||||
|
sourceQuery = "{ sequence(values: [5]) }"
|
||||||
|
in shouldResolveTo sourceQuery HashMap.empty expected
|
Reference in New Issue
Block a user