{-# LANGUAGE CPP #-}
#ifdef WITH_JSON
{-# LANGUAGE ExplicitForAll #-}
{-# LANGUAGE OverloadedStrings #-}
module Test.Hspec.GraphQL
( shouldResolve
, shouldResolveTo
) where
import Control.Monad.Catch (MonadCatch)
import qualified Data.Aeson as Aeson
import qualified Data.HashMap.Strict as HashMap
import Data.Text (Text)
import Language.GraphQL.Error
import Test.Hspec.Expectations (Expectation, expectationFailure, shouldBe, shouldNotSatisfy)
shouldResolveTo :: MonadCatch m
=> Either (ResponseEventStream m Aeson.Value) Aeson.Object
-> Aeson.Object
-> Expectation
shouldResolveTo :: Either (ResponseEventStream m Value) Object
-> Object -> Expectation
shouldResolveTo (Right Object
actual) Object
expected = Object
actual Object -> Object -> Expectation
forall a. (HasCallStack, Show a, Eq a) => a -> a -> Expectation
`shouldBe` Object
expected
shouldResolveTo Either (ResponseEventStream m Value) Object
_ Object
_ = HasCallStack => String -> Expectation
String -> Expectation
expectationFailure
String
"the query is expected to resolve to a value, but it resolved to an event stream"
shouldResolve :: MonadCatch m
=> (Text -> IO (Either (ResponseEventStream m Aeson.Value) Aeson.Object))
-> Text
-> Expectation
shouldResolve :: (Text -> IO (Either (ResponseEventStream m Value) Object))
-> Text -> Expectation
shouldResolve Text -> IO (Either (ResponseEventStream m Value) Object)
executor Text
query = do
Either (ResponseEventStream m Value) Object
actual <- Text -> IO (Either (ResponseEventStream m Value) Object)
executor Text
query
case Either (ResponseEventStream m Value) Object
actual of
Right Object
response ->
Object
response Object -> (Object -> Bool) -> Expectation
forall a. (HasCallStack, Show a) => a -> (a -> Bool) -> Expectation
`shouldNotSatisfy` Text -> Object -> Bool
forall k a. (Eq k, Hashable k) => k -> HashMap k a -> Bool
HashMap.member Text
"errors"
Either (ResponseEventStream m Value) Object
_ -> HasCallStack => String -> Expectation
String -> Expectation
expectationFailure
String
"the query is expected to resolve to a value, but it resolved to an event stream"
#else
module Test.Hspec.GraphQL
(
) where
#endif