Accept resolvers given by the user as is
This commit is contained in:
31
tests/Language/GraphQL/SchemaSpec.hs
Normal file
31
tests/Language/GraphQL/SchemaSpec.hs
Normal file
@ -0,0 +1,31 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Language.GraphQL.SchemaSpec
|
||||
( spec
|
||||
) where
|
||||
|
||||
import qualified Data.Aeson as Aeson
|
||||
import qualified Data.Aeson.Types as Aeson
|
||||
import qualified Data.Sequence as Sequence
|
||||
import Data.Text (Text)
|
||||
import Language.GraphQL.AST.Core
|
||||
import Language.GraphQL.Error
|
||||
import Language.GraphQL.Schema
|
||||
import Test.Hspec (Spec, describe, it, shouldBe)
|
||||
|
||||
spec :: Spec
|
||||
spec =
|
||||
describe "resolve" $
|
||||
it "ignores invalid __typename" $ do
|
||||
let resolver = object "__typename" $ pure
|
||||
[ scalar "field" $ pure ("T" :: Text)
|
||||
]
|
||||
schema = resolversToMap [resolver]
|
||||
fields = Sequence.singleton
|
||||
$ SelectionFragment
|
||||
$ Fragment "T" Sequence.empty
|
||||
expected = Aeson.object
|
||||
[ ("data" , Aeson.emptyObject)
|
||||
]
|
||||
|
||||
actual <- runCollectErrs (resolve schema fields)
|
||||
actual `shouldBe` expected
|
@ -4,7 +4,7 @@ module Test.DirectiveSpec
|
||||
( spec
|
||||
) where
|
||||
|
||||
import Data.Aeson (Value, object, (.=))
|
||||
import Data.Aeson (Value(..), object, (.=))
|
||||
import Data.HashMap.Strict (HashMap)
|
||||
import qualified Data.HashMap.Strict as HashMap
|
||||
import Data.List.NonEmpty (NonEmpty(..))
|
||||
|
@ -189,3 +189,27 @@ spec = do
|
||||
]
|
||||
actual <- graphql (HashMap.singleton "Query" $ garment "Hat" :| []) query
|
||||
actual `shouldBe` expected
|
||||
|
||||
it "test1" $ do
|
||||
let query = [r|
|
||||
{
|
||||
garment {
|
||||
circumference
|
||||
}
|
||||
}
|
||||
|]
|
||||
expected = object
|
||||
[ "data" .= object
|
||||
[ "garment" .= object
|
||||
[ "circumference" .= (60 :: Int)
|
||||
]
|
||||
]
|
||||
]
|
||||
actual <- graphql schema query
|
||||
actual `shouldBe` expected
|
||||
where
|
||||
schema = HashMap.singleton "Query" $ garment' :| []
|
||||
garment' = Schema.object "garment" $ return
|
||||
[ circumference'
|
||||
]
|
||||
circumference' = Schema.scalar "circumference" $ pure (60 :: Int)
|
||||
|
40
tests/Test/QuerySpec.hs
Normal file
40
tests/Test/QuerySpec.hs
Normal file
@ -0,0 +1,40 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
{-# LANGUAGE QuasiQuotes #-}
|
||||
module Test.QuerySpec
|
||||
( spec
|
||||
) where
|
||||
|
||||
import Data.Aeson ((.=), object)
|
||||
import qualified Data.HashMap.Strict as HashMap
|
||||
import Data.List.NonEmpty (NonEmpty(..))
|
||||
import Language.GraphQL
|
||||
import qualified Language.GraphQL.Schema as Schema
|
||||
import Test.Hspec (Spec, describe, it, shouldBe)
|
||||
import Text.RawString.QQ (r)
|
||||
|
||||
spec :: Spec
|
||||
spec =
|
||||
describe "Query executor" $
|
||||
it "returns objects from the root resolvers" $ do
|
||||
let query = [r|
|
||||
{
|
||||
garment {
|
||||
circumference
|
||||
}
|
||||
}
|
||||
|]
|
||||
expected = object
|
||||
[ "data" .= object
|
||||
[ "garment" .= object
|
||||
[ "circumference" .= (60 :: Int)
|
||||
]
|
||||
]
|
||||
]
|
||||
actual <- graphql schema query
|
||||
actual `shouldBe` expected
|
||||
where
|
||||
schema = HashMap.singleton "Query" $ garment' :| []
|
||||
garment' = Schema.object "garment" $ return
|
||||
[ circumference'
|
||||
]
|
||||
circumference' = Schema.scalar "circumference" $ pure (60 :: Int)
|
Reference in New Issue
Block a user