forked from OSS/graphql
Eugen Wissner
e24386402b
After the last commit there were a few places needed to be adjusted to support subscriptions. This is done and a test case is added. It is important to implement subscriptions now, because they require changes to the library API, and they are a big missing part to finish the executor. When the executor is finished, we can start to provide more stable API without breaking everything every release. Validation and introspection shouldn't require much changes to the API; AST would require some changes to report good errors after the validation - this is one thing I can think of. Fixes #5.
76 lines
2.5 KiB
Haskell
76 lines
2.5 KiB
Haskell
{- 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 #-}
|
|
{-# 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
|
|
{ query = Out.ObjectType "Query" Nothing [] hatFieldResolver
|
|
, mutation = Just $ Out.ObjectType "Mutation" Nothing [] incrementFieldResolver
|
|
, subscription = Nothing
|
|
}
|
|
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
|