Return a stream as well from graphql* functions
This commit is contained in:
@ -14,7 +14,8 @@ import qualified Data.HashMap.Strict as HashMap
|
||||
import Language.GraphQL
|
||||
import Language.GraphQL.Type
|
||||
import qualified Language.GraphQL.Type.Out as Out
|
||||
import Test.Hspec (Spec, describe, it, shouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Test.Hspec.GraphQL
|
||||
import Text.RawString.QQ (r)
|
||||
|
||||
experimentalResolver :: Schema IO
|
||||
@ -26,10 +27,8 @@ experimentalResolver = Schema
|
||||
$ Out.ValueResolver (Out.Field Nothing (Out.NamedScalarType int) mempty)
|
||||
$ pure $ Int 5
|
||||
|
||||
emptyObject :: Aeson.Value
|
||||
emptyObject = object
|
||||
[ "data" .= object []
|
||||
]
|
||||
emptyObject :: Aeson.Object
|
||||
emptyObject = HashMap.singleton "data" $ object []
|
||||
|
||||
spec :: Spec
|
||||
spec =
|
||||
@ -42,7 +41,7 @@ spec =
|
||||
|]
|
||||
|
||||
actual <- graphql experimentalResolver sourceQuery
|
||||
actual `shouldBe` emptyObject
|
||||
actual `shouldResolveTo` emptyObject
|
||||
|
||||
it "should not skip fields if @skip is false" $ do
|
||||
let sourceQuery = [r|
|
||||
@ -50,14 +49,12 @@ spec =
|
||||
experimentalField @skip(if: false)
|
||||
}
|
||||
|]
|
||||
expected = object
|
||||
[ "data" .= object
|
||||
expected = HashMap.singleton "data"
|
||||
$ object
|
||||
[ "experimentalField" .= (5 :: Int)
|
||||
]
|
||||
]
|
||||
|
||||
actual <- graphql experimentalResolver sourceQuery
|
||||
actual `shouldBe` expected
|
||||
actual `shouldResolveTo` expected
|
||||
|
||||
it "should skip fields if @include is false" $ do
|
||||
let sourceQuery = [r|
|
||||
@ -67,7 +64,7 @@ spec =
|
||||
|]
|
||||
|
||||
actual <- graphql experimentalResolver sourceQuery
|
||||
actual `shouldBe` emptyObject
|
||||
actual `shouldResolveTo` emptyObject
|
||||
|
||||
it "should be able to @skip a fragment spread" $ do
|
||||
let sourceQuery = [r|
|
||||
@ -81,7 +78,7 @@ spec =
|
||||
|]
|
||||
|
||||
actual <- graphql experimentalResolver sourceQuery
|
||||
actual `shouldBe` emptyObject
|
||||
actual `shouldResolveTo` emptyObject
|
||||
|
||||
it "should be able to @skip an inline fragment" $ do
|
||||
let sourceQuery = [r|
|
||||
@ -93,4 +90,4 @@ spec =
|
||||
|]
|
||||
|
||||
actual <- graphql experimentalResolver sourceQuery
|
||||
actual `shouldBe` emptyObject
|
||||
actual `shouldResolveTo` emptyObject
|
||||
|
@ -8,20 +8,15 @@ module Test.FragmentSpec
|
||||
( spec
|
||||
) where
|
||||
|
||||
import Data.Aeson (object, (.=))
|
||||
import Data.Aeson ((.=))
|
||||
import qualified Data.Aeson as Aeson
|
||||
import qualified Data.HashMap.Strict as HashMap
|
||||
import Data.Text (Text)
|
||||
import Language.GraphQL
|
||||
import Language.GraphQL.Type
|
||||
import qualified Language.GraphQL.Type.Out as Out
|
||||
import Test.Hspec
|
||||
( Spec
|
||||
, describe
|
||||
, it
|
||||
, shouldBe
|
||||
, shouldNotSatisfy
|
||||
)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Test.Hspec.GraphQL
|
||||
import Text.RawString.QQ (r)
|
||||
|
||||
size :: (Text, Value)
|
||||
@ -50,10 +45,6 @@ inlineQuery = [r|{
|
||||
}
|
||||
}|]
|
||||
|
||||
hasErrors :: Aeson.Value -> Bool
|
||||
hasErrors (Aeson.Object object') = HashMap.member "errors" object'
|
||||
hasErrors _ = True
|
||||
|
||||
shirtType :: Out.ObjectType IO
|
||||
shirtType = Out.ObjectType "Shirt" Nothing []
|
||||
$ HashMap.fromList
|
||||
@ -100,25 +91,23 @@ 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 = object
|
||||
[ "data" .= object
|
||||
[ "garment" .= object
|
||||
let expected = HashMap.singleton "data"
|
||||
$ Aeson.object
|
||||
[ "garment" .= Aeson.object
|
||||
[ "circumference" .= (60 :: Int)
|
||||
]
|
||||
]
|
||||
]
|
||||
in actual `shouldBe` expected
|
||||
in actual `shouldResolveTo` expected
|
||||
|
||||
it "chooses the last selection if the type matches" $ do
|
||||
actual <- graphql (toSchema "Shirt" $ garment "Shirt") inlineQuery
|
||||
let expected = object
|
||||
[ "data" .= object
|
||||
[ "garment" .= object
|
||||
let expected = HashMap.singleton "data"
|
||||
$ Aeson.object
|
||||
[ "garment" .= Aeson.object
|
||||
[ "size" .= ("L" :: Text)
|
||||
]
|
||||
]
|
||||
]
|
||||
in actual `shouldBe` expected
|
||||
in actual `shouldResolveTo` expected
|
||||
|
||||
it "embeds inline fragments without type" $ do
|
||||
let sourceQuery = [r|{
|
||||
@ -132,15 +121,14 @@ spec = do
|
||||
resolvers = ("garment", Object $ HashMap.fromList [circumference, size])
|
||||
|
||||
actual <- graphql (toSchema "garment" resolvers) sourceQuery
|
||||
let expected = object
|
||||
[ "data" .= object
|
||||
[ "garment" .= object
|
||||
let expected = HashMap.singleton "data"
|
||||
$ Aeson.object
|
||||
[ "garment" .= Aeson.object
|
||||
[ "circumference" .= (60 :: Int)
|
||||
, "size" .= ("L" :: Text)
|
||||
]
|
||||
]
|
||||
]
|
||||
in actual `shouldBe` expected
|
||||
in actual `shouldResolveTo` expected
|
||||
|
||||
it "evaluates fragments on Query" $ do
|
||||
let sourceQuery = [r|{
|
||||
@ -148,9 +136,7 @@ spec = do
|
||||
size
|
||||
}
|
||||
}|]
|
||||
|
||||
actual <- graphql (toSchema "size" size) sourceQuery
|
||||
actual `shouldNotSatisfy` hasErrors
|
||||
in graphql (toSchema "size" size) `shouldResolve` sourceQuery
|
||||
|
||||
describe "Fragment spread executor" $ do
|
||||
it "evaluates fragment spreads" $ do
|
||||
@ -165,12 +151,11 @@ spec = do
|
||||
|]
|
||||
|
||||
actual <- graphql (toSchema "circumference" circumference) sourceQuery
|
||||
let expected = object
|
||||
[ "data" .= object
|
||||
let expected = HashMap.singleton "data"
|
||||
$ Aeson.object
|
||||
[ "circumference" .= (60 :: Int)
|
||||
]
|
||||
]
|
||||
in actual `shouldBe` expected
|
||||
in actual `shouldResolveTo` expected
|
||||
|
||||
it "evaluates nested fragments" $ do
|
||||
let sourceQuery = [r|
|
||||
@ -190,19 +175,16 @@ spec = do
|
||||
|]
|
||||
|
||||
actual <- graphql (toSchema "Hat" $ garment "Hat") sourceQuery
|
||||
let expected = object
|
||||
[ "data" .= object
|
||||
[ "garment" .= object
|
||||
let expected = HashMap.singleton "data"
|
||||
$ Aeson.object
|
||||
[ "garment" .= Aeson.object
|
||||
[ "circumference" .= (60 :: Int)
|
||||
]
|
||||
]
|
||||
]
|
||||
in actual `shouldBe` expected
|
||||
in actual `shouldResolveTo` expected
|
||||
|
||||
it "rejects recursive fragments" $ do
|
||||
let expected = object
|
||||
[ "data" .= object []
|
||||
]
|
||||
let expected = HashMap.singleton "data" $ Aeson.object []
|
||||
sourceQuery = [r|
|
||||
{
|
||||
...circumferenceFragment
|
||||
@ -214,7 +196,7 @@ spec = do
|
||||
|]
|
||||
|
||||
actual <- graphql (toSchema "circumference" circumference) sourceQuery
|
||||
actual `shouldBe` expected
|
||||
actual `shouldResolveTo` expected
|
||||
|
||||
it "considers type condition" $ do
|
||||
let sourceQuery = [r|
|
||||
@ -231,12 +213,11 @@ spec = do
|
||||
size
|
||||
}
|
||||
|]
|
||||
expected = object
|
||||
[ "data" .= object
|
||||
[ "garment" .= object
|
||||
expected = HashMap.singleton "data"
|
||||
$ Aeson.object
|
||||
[ "garment" .= Aeson.object
|
||||
[ "circumference" .= (60 :: Int)
|
||||
]
|
||||
]
|
||||
]
|
||||
actual <- graphql (toSchema "Hat" $ garment "Hat") sourceQuery
|
||||
actual `shouldBe` expected
|
||||
actual `shouldResolveTo` expected
|
||||
|
@ -11,10 +11,11 @@ module Test.RootOperationSpec
|
||||
import Data.Aeson ((.=), object)
|
||||
import qualified Data.HashMap.Strict as HashMap
|
||||
import Language.GraphQL
|
||||
import Test.Hspec (Spec, describe, it, shouldBe)
|
||||
import Test.Hspec (Spec, describe, it)
|
||||
import Text.RawString.QQ (r)
|
||||
import Language.GraphQL.Type
|
||||
import qualified Language.GraphQL.Type.Out as Out
|
||||
import Test.Hspec.GraphQL
|
||||
|
||||
hatType :: Out.ObjectType IO
|
||||
hatType = Out.ObjectType "Hat" Nothing []
|
||||
@ -50,15 +51,14 @@ spec =
|
||||
}
|
||||
}
|
||||
|]
|
||||
expected = object
|
||||
[ "data" .= object
|
||||
expected = HashMap.singleton "data"
|
||||
$ object
|
||||
[ "garment" .= object
|
||||
[ "circumference" .= (60 :: Int)
|
||||
]
|
||||
]
|
||||
]
|
||||
actual <- graphql schema querySource
|
||||
actual `shouldBe` expected
|
||||
actual `shouldResolveTo` expected
|
||||
|
||||
it "chooses Mutation" $ do
|
||||
let querySource = [r|
|
||||
@ -66,10 +66,9 @@ spec =
|
||||
incrementCircumference
|
||||
}
|
||||
|]
|
||||
expected = object
|
||||
[ "data" .= object
|
||||
expected = HashMap.singleton "data"
|
||||
$ object
|
||||
[ "incrementCircumference" .= (61 :: Int)
|
||||
]
|
||||
]
|
||||
actual <- graphql schema querySource
|
||||
actual `shouldBe` expected
|
||||
actual `shouldResolveTo` expected
|
||||
|
@ -357,10 +357,10 @@ spec = describe "Star Wars Query Tests" $ do
|
||||
|
||||
testQuery :: Text -> Aeson.Value -> Expectation
|
||||
testQuery q expected =
|
||||
let Right actual = graphql schema q
|
||||
in actual `shouldBe` expected
|
||||
let Right (Right actual) = graphql schema q
|
||||
in Aeson.Object actual `shouldBe` expected
|
||||
|
||||
testQueryParams :: Aeson.Object -> Text -> Aeson.Value -> Expectation
|
||||
testQueryParams f q expected =
|
||||
let Right actual = graphqlSubs schema Nothing f q
|
||||
in actual `shouldBe` expected
|
||||
let Right (Right actual) = graphqlSubs schema Nothing f q
|
||||
in Aeson.Object actual `shouldBe` expected
|
||||
|
Reference in New Issue
Block a user