graphql/tests/Test/RootOperationSpec.hs
Eugen Wissner ae2210f659 Support subscriptions
This is experimental support.
The implementation is based on conduit and is boring. There is a new
resolver data constructor that should create a source event stream. The
executor receives the events, pipes them through the normal execution
and puts them into the response stream which is returned to the user.

- Tests are missing.
- The executor should check field value resolver on subscription types.
- The graphql function should probably return (Either
  ResponseEventStream Response), but I'm not sure about this. It will
  make the usage more complicated if no subscriptions are involved, but
  with the current API implementing subscriptions is more
  difficult than it should be.
2020-07-14 19:37:56 +02:00

70 lines
2.2 KiB
Haskell

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Test.RootOperationSpec
( spec
) where
import Data.Aeson ((.=), object)
import qualified Data.HashMap.Strict as HashMap
import Language.GraphQL
import Test.Hspec (Spec, describe, it, shouldBe)
import Text.RawString.QQ (r)
import Language.GraphQL.Type
import qualified Language.GraphQL.Type.Out as Out
hatType :: Out.ObjectType IO
hatType = Out.ObjectType "Hat" Nothing []
$ HashMap.singleton "circumference"
$ ValueResolver (Out.Field Nothing (Out.NamedScalarType int) mempty)
$ pure $ Int 60
schema :: Schema IO
schema = Schema
(Out.ObjectType "Query" Nothing [] hatFieldResolver)
(Just $ Out.ObjectType "Mutation" Nothing [] incrementFieldResolver)
where
garment = pure $ Object $ HashMap.fromList
[ ("circumference", Int 60)
]
incrementFieldResolver = HashMap.singleton "incrementCircumference"
$ ValueResolver (Out.Field Nothing (Out.NamedScalarType int) mempty)
$ pure $ Int 61
hatField = Out.Field Nothing (Out.NamedObjectType hatType) mempty
hatFieldResolver =
HashMap.singleton "garment" $ ValueResolver hatField garment
spec :: Spec
spec =
describe "Root operation type" $ do
it "returns objects from the root resolvers" $ do
let querySource = [r|
{
garment {
circumference
}
}
|]
expected = object
[ "data" .= object
[ "garment" .= object
[ "circumference" .= (60 :: Int)
]
]
]
actual <- graphql schema querySource
actual `shouldBe` expected
it "chooses Mutation" $ do
let querySource = [r|
mutation {
incrementCircumference
}
|]
expected = object
[ "data" .= object
[ "incrementCircumference" .= (61 :: Int)
]
]
actual <- graphql schema querySource
actual `shouldBe` expected