1
Fork 0

Put test helpers into Test.Hspec.GraphQL

This commit is contained in:
Eugen Wissner 2022-03-23 21:58:12 +01:00
parent 0cf459b8eb
commit c93c64a7f4
No known key found for this signature in database
GPG key ID: A27FDC1E8EE902C0
8 changed files with 198 additions and 148 deletions

View file

@ -4,19 +4,21 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE PackageImports #-}
module Language.GraphQL.DirectiveSpec
( spec
) where
import Data.Aeson (object, (.=))
import qualified Data.Aeson as Aeson
import Language.GraphQL.AST.Document (Name)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Language.GraphQL.Foundation
import qualified Language.GraphQL as GraphQL
import Language.GraphQL.TH
import Language.GraphQL.Type
import qualified Language.GraphQL.Type.Out as Out
import Test.Hspec (Spec, describe, it)
import Test.Hspec.GraphQL
import "graphql-spice" Test.Hspec.GraphQL
experimentalResolver :: Schema IO
experimentalResolver = schema queryType Nothing Nothing mempty
@ -26,9 +28,6 @@ experimentalResolver = schema queryType Nothing Nothing mempty
$ Out.ValueResolver (Out.Field Nothing (Out.NamedScalarType int) mempty)
$ pure $ Int 5
emptyObject :: Aeson.Object
emptyObject = HashMap.singleton "data" $ object []
spec :: Spec
spec =
describe "Directive executor" $ do
@ -39,8 +38,8 @@ spec =
}
|]
actual <- graphql experimentalResolver sourceQuery
actual `shouldResolveTo` emptyObject
actual <- GraphQL.graphql experimentalResolver Nothing (mempty :: HashMap Name Value) sourceQuery
actual `shouldResolveTo` Object mempty
it "should not skip fields if @skip is false" $ do
let sourceQuery = [gql|
@ -48,11 +47,8 @@ spec =
experimentalField @skip(if: false)
}
|]
expected = HashMap.singleton "data"
$ object
[ "experimentalField" .= (5 :: Int)
]
actual <- graphql experimentalResolver sourceQuery
expected = Object $ HashMap.singleton "experimentalField" (Int 5)
actual <- GraphQL.graphql experimentalResolver Nothing (mempty :: HashMap Name Value) sourceQuery
actual `shouldResolveTo` expected
it "should skip fields if @include is false" $ do
@ -62,8 +58,8 @@ spec =
}
|]
actual <- graphql experimentalResolver sourceQuery
actual `shouldResolveTo` emptyObject
actual <- GraphQL.graphql experimentalResolver Nothing (mempty :: HashMap Name Value) sourceQuery
actual `shouldResolveTo` Object mempty
it "should be able to @skip a fragment spread" $ do
let sourceQuery = [gql|
@ -76,8 +72,8 @@ spec =
}
|]
actual <- graphql experimentalResolver sourceQuery
actual `shouldResolveTo` emptyObject
actual <- GraphQL.graphql experimentalResolver Nothing (mempty :: HashMap Name Value) sourceQuery
actual `shouldResolveTo` Object mempty
it "should be able to @skip an inline fragment" $ do
let sourceQuery = [gql|
@ -88,5 +84,5 @@ spec =
}
|]
actual <- graphql experimentalResolver sourceQuery
actual `shouldResolveTo` emptyObject
actual <- GraphQL.graphql experimentalResolver Nothing (mempty :: HashMap Name Value) sourceQuery
actual `shouldResolveTo` Object mempty

View file

@ -4,20 +4,23 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE PackageImports #-}
module Language.GraphQL.FragmentSpec
( spec
) where
import Data.Aeson ((.=))
import qualified Data.Aeson as Aeson
import qualified Data.HashMap.Strict as HashMap
import Data.Text (Text)
import Language.GraphQL.Foundation
import Language.GraphQL.AST (Name)
import Data.HashMap.Strict (HashMap)
import Language.GraphQL.Type
import Language.GraphQL.Error
import qualified Language.GraphQL.Type.Out as Out
import Language.GraphQL.TH
import qualified Language.GraphQL as GraphQL
import Test.Hspec (Spec, describe, it)
import Test.Hspec.GraphQL
import "graphql-spice" Test.Hspec.GraphQL
size :: (Text, Value)
size = ("size", String "L")
@ -88,23 +91,23 @@ spec :: Spec
spec = do
describe "Inline fragment executor" $ do
it "chooses the first selection if the type matches" $ do
actual <- graphql (toSchema "Hat" $ garment "Hat") inlineQuery
let expected = HashMap.singleton "data"
$ Aeson.object
[ "garment" .= Aeson.object
[ "circumference" .= (60 :: Int)
]
]
let localSchema = toSchema "Hat" $ garment "Hat"
actual <- GraphQL.graphql localSchema Nothing (mempty :: HashMap Name Value) inlineQuery
let expected = Object
$ HashMap.singleton "garment"
$ Object
$ HashMap.singleton "circumference"
$ Int 60
in actual `shouldResolveTo` expected
it "chooses the last selection if the type matches" $ do
actual <- graphql (toSchema "Shirt" $ garment "Shirt") inlineQuery
let expected = HashMap.singleton "data"
$ Aeson.object
[ "garment" .= Aeson.object
[ "size" .= ("L" :: Text)
]
]
let localSchema = toSchema "Shirt" $ garment "Shirt"
actual <- GraphQL.graphql localSchema Nothing (mempty :: HashMap Name Value) inlineQuery
let expected = Object
$ HashMap.singleton "garment"
$ Object
$ HashMap.singleton "size"
$ String "L"
in actual `shouldResolveTo` expected
it "embeds inline fragments without type" $ do
@ -116,12 +119,12 @@ spec = do
}
}
|]
actual <- graphql (toSchema "circumference" circumference) sourceQuery
let expected = HashMap.singleton "data"
$ Aeson.object
[ "circumference" .= (60 :: Int)
, "size" .= ("L" :: Text)
]
let localSchema = toSchema "circumference" circumference
actual <- GraphQL.graphql localSchema Nothing (mempty :: HashMap Name Value) sourceQuery
let expected = Object $ HashMap.fromList
[ ("circumference", Int 60)
, ("size", String "L")
]
in actual `shouldResolveTo` expected
it "evaluates fragments on Query" $ do
@ -132,7 +135,10 @@ spec = do
}
}
|]
in graphql (toSchema "size" size) `shouldResolve` sourceQuery
localSchema = toSchema "size" size
actual :: Text -> IO (Either (ResponseEventStream IO Value) (Response Value))
actual = GraphQL.graphql localSchema Nothing (mempty :: HashMap Name Value)
in actual `shouldResolve` sourceQuery
describe "Fragment spread executor" $ do
it "evaluates fragment spreads" $ do
@ -145,12 +151,11 @@ spec = do
circumference
}
|]
actual <- graphql (toSchema "circumference" circumference) sourceQuery
let expected = HashMap.singleton "data"
$ Aeson.object
[ "circumference" .= (60 :: Int)
]
let localSchema = toSchema "circumference" circumference
actual <- GraphQL.graphql localSchema Nothing (mempty :: HashMap Name Value) sourceQuery
let expected = Object
$ HashMap.singleton "circumference"
$ Int 60
in actual `shouldResolveTo` expected
it "evaluates nested fragments" $ do
@ -169,14 +174,13 @@ spec = do
circumference
}
|]
actual <- graphql (toSchema "Hat" $ garment "Hat") sourceQuery
let expected = HashMap.singleton "data"
$ Aeson.object
[ "garment" .= Aeson.object
[ "circumference" .= (60 :: Int)
]
]
let localSchema = toSchema "Hat" $ garment "Hat"
actual <- GraphQL.graphql localSchema Nothing (mempty :: HashMap Name Value) sourceQuery
let expected = Object
$ HashMap.singleton "garment"
$ Object
$ HashMap.singleton "circumference"
$ Int 60
in actual `shouldResolveTo` expected
it "considers type condition" $ do
@ -194,11 +198,11 @@ spec = do
size
}
|]
expected = HashMap.singleton "data"
$ Aeson.object
[ "garment" .= Aeson.object
[ "circumference" .= (60 :: Int)
]
]
actual <- graphql (toSchema "Hat" $ garment "Hat") sourceQuery
expected = Object
$ HashMap.singleton "garment"
$ Object
$ HashMap.singleton "circumference"
$ Int 60
let localSchema = toSchema "Hat" $ garment "Hat"
actual <- GraphQL.graphql localSchema Nothing (mempty :: HashMap Name Value) sourceQuery
actual `shouldResolveTo` expected

View file

@ -4,18 +4,21 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
{-# LANGUAGE PackageImports #-}
module Language.GraphQL.RootOperationSpec
( spec
) where
import Data.Aeson ((.=), object)
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Language.GraphQL.Foundation
import Language.GraphQL
import Language.GraphQL.AST (Name)
import Test.Hspec (Spec, describe, it)
import Language.GraphQL.TH
import Language.GraphQL.Type
import qualified Language.GraphQL.Type.Out as Out
import Test.Hspec.GraphQL
import "graphql-spice" Test.Hspec.GraphQL
hatType :: Out.ObjectType IO
hatType = Out.ObjectType "Hat" Nothing []
@ -49,13 +52,12 @@ spec =
}
}
|]
expected = HashMap.singleton "data"
$ object
[ "garment" .= object
[ "circumference" .= (60 :: Int)
]
]
actual <- graphql garmentSchema querySource
expected = Object
$ HashMap.singleton "garment"
$ Object
$ HashMap.singleton "circumference"
$ Int 60
actual <- graphql garmentSchema Nothing (mempty :: HashMap Name Value) querySource
actual `shouldResolveTo` expected
it "chooses Mutation" $ do
@ -64,9 +66,8 @@ spec =
incrementCircumference
}
|]
expected = HashMap.singleton "data"
$ object
[ "incrementCircumference" .= (61 :: Int)
]
actual <- graphql garmentSchema querySource
expected = Object
$ HashMap.singleton "incrementCircumference"
$ Int 61
actual <- graphql garmentSchema Nothing (mempty :: HashMap Name Value) querySource
actual `shouldResolveTo` expected