Put test helpers into Test.Hspec.GraphQL

This commit is contained in:
2022-03-23 21:58:12 +01:00
parent 0cf459b8eb
commit c93c64a7f4
8 changed files with 198 additions and 148 deletions

View File

@ -1,58 +0,0 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
module Language.GraphQL.Foundation
( module Language.GraphQL.Serialize
, graphql
) where
import Language.GraphQL.Serialize
import Control.Monad.Catch (MonadCatch)
import qualified Data.Aeson as Aeson
import qualified Data.Aeson.Types as Aeson
import Data.HashMap.Strict (HashMap)
import qualified Data.Aeson.KeyMap as KeyMap
import Data.Maybe (catMaybes)
import qualified Data.Sequence as Seq
import Data.Text (Text)
import Data.Vector (Vector)
import qualified Data.Vector as Vector
import qualified Language.GraphQL as GraphQL
import Language.GraphQL.AST
import Language.GraphQL.Error
import Language.GraphQL.Type.Schema (Schema)
import Data.Bifunctor (Bifunctor(..))
-- | If the text parses correctly as a @GraphQL@ query the query is
-- executed using the given 'Schema'.
graphql :: MonadCatch m
=> Schema m -- ^ Resolvers.
-> Text -- ^ Text representing a @GraphQL@ request document.
-> m (Either (ResponseEventStream m Aeson.Value) Aeson.Object) -- ^ Response.
graphql schema = fmap (bimap stream formatResponse)
. GraphQL.graphql schema mempty (mempty :: HashMap Name JSON)
where
stream :: ResponseEventStream m JSON -> ResponseEventStream m Aeson.Value
stream = undefined
formatResponse :: Response JSON -> Aeson.Object
formatResponse Response{ errors, data' = JSON json } =
let dataResponse = KeyMap.singleton "data" json
in case errors of
Seq.Empty -> dataResponse
_ -> flip (KeyMap.insert "errors") dataResponse
$ Aeson.Array $ foldr fromError mempty errors
fromError :: Error -> Vector Aeson.Value -> Vector Aeson.Value
fromError Error{..} = Vector.cons $ Aeson.object $ catMaybes
[ Just ("message", Aeson.String message)
, toMaybe fromLocation "locations" locations
, toMaybe fromPath "path" path
]
fromPath (Segment segment) = Aeson.String segment
fromPath (Index index) = Aeson.toJSON index
fromLocation Location{..} = Aeson.object
[ ("line", Aeson.toJSON line)
, ("column", Aeson.toJSON column)
]
toMaybe _ _ [] = Nothing
toMaybe f key xs = Just (key, Aeson.listValue f xs)

View File

@ -1,17 +1,30 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
module Language.GraphQL.Serialize
module Language.GraphQL.JSON
( JSON(..)
, graphql
) where
import qualified Data.Aeson as Aeson
import Control.Monad.Catch (MonadCatch)
import qualified Data.Aeson.Types as Aeson
import Data.Maybe (catMaybes)
import qualified Data.Sequence as Seq
import Data.Vector (Vector)
import qualified Data.Vector as Vector
import qualified Language.GraphQL as GraphQL
import Language.GraphQL.AST (Location(..), Name)
import Language.GraphQL.Error
import Language.GraphQL.Type.Schema (Schema)
import Data.Bifunctor (Bifunctor(..))
import qualified Conduit
import qualified Data.Aeson.Key as Aeson.Key
import qualified Data.Aeson.KeyMap as KeyMap
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
import Data.Scientific (toBoundedInteger, toRealFloat)
import Data.Text (Text)
import Language.GraphQL.AST (Name)
import Language.GraphQL.Execute.Coerce
import qualified Language.GraphQL.Execute.OrderedMap as OrderedMap
import qualified Language.GraphQL.Type.In as In
@ -100,3 +113,41 @@ instance VariableValue JSON where
coerced <- coerceVariableValue listType $ JSON variableValue
pure $ coerced : list
coerceVariableValue _ _ = Nothing
-- | If the text parses correctly as a @GraphQL@ query the query is
-- executed using the given 'Schema'.
graphql :: MonadCatch m
=> Schema m -- ^ Resolvers.
-> Maybe Text -- ^ Operation name.
-> Aeson.Object -- ^ Variables.
-> Text -- ^ Text representing a @GraphQL@ request document.
-> m (Either (ResponseEventStream m Aeson.Value) Aeson.Object) -- ^ Response.
graphql schema operationName variableValues = fmap (bimap stream formatResponse)
. GraphQL.graphql schema operationName jsonVariables
where
jsonVariables = JSON <$> KeyMap.toHashMapText variableValues
-- stream :: ResponseEventStream m JSON -> ResponseEventStream m Aeson.Value
stream = Conduit.mapOutput mapResponse
mapResponse response@Response{ data' = JSON json } =
response{ data' = json }
formatResponse :: Response JSON -> Aeson.Object
formatResponse Response{ errors, data' = JSON json } =
let dataResponse = KeyMap.singleton "data" json
in case errors of
Seq.Empty -> dataResponse
_ -> flip (KeyMap.insert "errors") dataResponse
$ Aeson.Array $ foldr fromError mempty errors
fromError :: Error -> Vector Aeson.Value -> Vector Aeson.Value
fromError Error{..} = Vector.cons $ Aeson.object $ catMaybes
[ Just ("message", Aeson.String message)
, toMaybe fromLocation "locations" locations
, toMaybe fromPath "path" path
]
fromPath (Segment segment) = Aeson.String segment
fromPath (Index index) = Aeson.toJSON index
fromLocation Location{..} = Aeson.object
[ ("line", Aeson.toJSON line)
, ("column", Aeson.toJSON column)
]
toMaybe _ _ [] = Nothing
toMaybe f key xs = Just (key, Aeson.listValue f xs)

48
src/Test/Hspec/GraphQL.hs Normal file
View File

@ -0,0 +1,48 @@
{- 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 ExplicitForAll #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DuplicateRecordFields #-}
-- | Test helpers.
module Test.Hspec.GraphQL
( shouldResolve
, shouldResolveTo
) where
import Control.Monad.Catch (MonadCatch)
import qualified Data.Sequence as Seq
import Data.Text (Text)
import Language.GraphQL.Error
import Language.GraphQL.Execute
import Test.Hspec.Expectations
( Expectation
, expectationFailure
, shouldBe
, shouldSatisfy
)
-- | Asserts that a query resolves to some value.
shouldResolveTo :: (MonadCatch m, Serialize b, Eq b, Show b)
=> Either (ResponseEventStream m b) (Response b)
-> b
-> Expectation
shouldResolveTo (Right Response{ errors = Seq.Empty, data' }) expected =
data' `shouldBe` expected
shouldResolveTo _ _ = expectationFailure
"the query is expected to resolve to a value, but it resolved to an event stream"
-- | Asserts that the response doesn't contain any errors.
shouldResolve :: (MonadCatch m, Serialize b)
=> (Text -> IO (Either (ResponseEventStream m b) (Response b)))
-> Text
-> Expectation
shouldResolve executor query = do
actual <- executor query
case actual of
Right Response{ errors } -> errors `shouldSatisfy` Seq.null
_ -> expectationFailure
"the query is expected to resolve to a value, but it resolved to an event stream"