2020-07-15 19:15:31 +02:00
|
|
|
{- 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/. -}
|
|
|
|
|
2019-09-13 20:33:39 +02:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
{-# LANGUAGE QuasiQuotes #-}
|
|
|
|
module Test.FragmentSpec
|
|
|
|
( spec
|
|
|
|
) where
|
|
|
|
|
2020-07-19 07:36:06 +02:00
|
|
|
import Data.Aeson ((.=))
|
2020-05-27 23:18:35 +02:00
|
|
|
import qualified Data.Aeson as Aeson
|
2019-10-19 10:00:25 +02:00
|
|
|
import qualified Data.HashMap.Strict as HashMap
|
2019-09-13 20:33:39 +02:00
|
|
|
import Data.Text (Text)
|
|
|
|
import Language.GraphQL
|
2020-06-19 10:53:41 +02:00
|
|
|
import Language.GraphQL.Type
|
2020-05-24 13:51:00 +02:00
|
|
|
import qualified Language.GraphQL.Type.Out as Out
|
2020-07-19 07:36:06 +02:00
|
|
|
import Test.Hspec (Spec, describe, it)
|
|
|
|
import Test.Hspec.GraphQL
|
2019-09-13 20:33:39 +02:00
|
|
|
import Text.RawString.QQ (r)
|
|
|
|
|
2020-05-27 23:18:35 +02:00
|
|
|
size :: (Text, Value)
|
|
|
|
size = ("size", String "L")
|
2019-09-13 20:33:39 +02:00
|
|
|
|
2020-05-27 23:18:35 +02:00
|
|
|
circumference :: (Text, Value)
|
|
|
|
circumference = ("circumference", Int 60)
|
2019-09-13 20:33:39 +02:00
|
|
|
|
2020-05-27 23:18:35 +02:00
|
|
|
garment :: Text -> (Text, Value)
|
|
|
|
garment typeName =
|
|
|
|
("garment", Object $ HashMap.fromList
|
|
|
|
[ if typeName == "Hat" then circumference else size
|
|
|
|
, ("__typename", String typeName)
|
|
|
|
]
|
|
|
|
)
|
2019-09-13 20:33:39 +02:00
|
|
|
|
|
|
|
inlineQuery :: Text
|
|
|
|
inlineQuery = [r|{
|
|
|
|
garment {
|
|
|
|
... on Hat {
|
|
|
|
circumference
|
|
|
|
}
|
|
|
|
... on Shirt {
|
|
|
|
size
|
|
|
|
}
|
|
|
|
}
|
|
|
|
}|]
|
|
|
|
|
2020-05-25 07:41:21 +02:00
|
|
|
shirtType :: Out.ObjectType IO
|
2020-05-26 11:13:55 +02:00
|
|
|
shirtType = Out.ObjectType "Shirt" Nothing []
|
2020-05-27 23:18:35 +02:00
|
|
|
$ HashMap.fromList
|
2020-06-29 13:14:23 +02:00
|
|
|
[ ("size", sizeFieldType)
|
|
|
|
, ("circumference", circumferenceFieldType)
|
2020-05-27 23:18:35 +02:00
|
|
|
]
|
2020-05-21 10:20:59 +02:00
|
|
|
|
2020-05-25 07:41:21 +02:00
|
|
|
hatType :: Out.ObjectType IO
|
2020-05-26 11:13:55 +02:00
|
|
|
hatType = Out.ObjectType "Hat" Nothing []
|
2020-05-27 23:18:35 +02:00
|
|
|
$ HashMap.fromList
|
2020-06-29 13:14:23 +02:00
|
|
|
[ ("size", sizeFieldType)
|
|
|
|
, ("circumference", circumferenceFieldType)
|
2020-05-27 23:18:35 +02:00
|
|
|
]
|
|
|
|
|
2020-07-14 19:37:56 +02:00
|
|
|
circumferenceFieldType :: Out.Resolver IO
|
|
|
|
circumferenceFieldType
|
|
|
|
= Out.ValueResolver (Out.Field Nothing (Out.NamedScalarType int) mempty)
|
2020-06-29 13:14:23 +02:00
|
|
|
$ pure $ snd circumference
|
2020-06-03 07:20:38 +02:00
|
|
|
|
2020-07-14 19:37:56 +02:00
|
|
|
sizeFieldType :: Out.Resolver IO
|
|
|
|
sizeFieldType
|
|
|
|
= Out.ValueResolver (Out.Field Nothing (Out.NamedScalarType string) mempty)
|
2020-06-29 13:14:23 +02:00
|
|
|
$ pure $ snd size
|
2020-06-03 07:20:38 +02:00
|
|
|
|
2020-05-27 23:18:35 +02:00
|
|
|
toSchema :: Text -> (Text, Value) -> Schema IO
|
|
|
|
toSchema t (_, resolve) = Schema
|
2020-07-15 19:15:31 +02:00
|
|
|
{ query = queryType, mutation = Nothing, subscription = Nothing }
|
2020-05-14 09:17:14 +02:00
|
|
|
where
|
2020-05-27 23:18:35 +02:00
|
|
|
unionMember = if t == "Hat" then hatType else shirtType
|
2020-06-03 07:20:38 +02:00
|
|
|
typeNameField = Out.Field Nothing (Out.NamedScalarType string) mempty
|
|
|
|
garmentField = Out.Field Nothing (Out.NamedObjectType unionMember) mempty
|
2020-05-27 23:18:35 +02:00
|
|
|
queryType =
|
|
|
|
case t of
|
|
|
|
"circumference" -> hatType
|
|
|
|
"size" -> shirtType
|
|
|
|
_ -> Out.ObjectType "Query" Nothing []
|
|
|
|
$ HashMap.fromList
|
2020-07-14 19:37:56 +02:00
|
|
|
[ ("garment", ValueResolver garmentField (pure resolve))
|
|
|
|
, ("__typename", ValueResolver typeNameField (pure $ String "Shirt"))
|
2020-05-27 23:18:35 +02:00
|
|
|
]
|
2020-05-14 09:17:14 +02:00
|
|
|
|
2019-09-13 20:33:39 +02:00
|
|
|
spec :: Spec
|
2019-12-01 20:43:19 +01:00
|
|
|
spec = do
|
|
|
|
describe "Inline fragment executor" $ do
|
|
|
|
it "chooses the first selection if the type matches" $ do
|
2020-05-27 23:18:35 +02:00
|
|
|
actual <- graphql (toSchema "Hat" $ garment "Hat") inlineQuery
|
2020-07-19 07:36:06 +02:00
|
|
|
let expected = HashMap.singleton "data"
|
|
|
|
$ Aeson.object
|
|
|
|
[ "garment" .= Aeson.object
|
2019-12-01 20:43:19 +01:00
|
|
|
[ "circumference" .= (60 :: Int)
|
|
|
|
]
|
|
|
|
]
|
2020-07-19 07:36:06 +02:00
|
|
|
in actual `shouldResolveTo` expected
|
2019-12-01 20:43:19 +01:00
|
|
|
|
|
|
|
it "chooses the last selection if the type matches" $ do
|
2020-05-27 23:18:35 +02:00
|
|
|
actual <- graphql (toSchema "Shirt" $ garment "Shirt") inlineQuery
|
2020-07-19 07:36:06 +02:00
|
|
|
let expected = HashMap.singleton "data"
|
|
|
|
$ Aeson.object
|
|
|
|
[ "garment" .= Aeson.object
|
2019-12-01 20:43:19 +01:00
|
|
|
[ "size" .= ("L" :: Text)
|
|
|
|
]
|
2019-10-07 21:03:07 +02:00
|
|
|
]
|
2020-07-19 07:36:06 +02:00
|
|
|
in actual `shouldResolveTo` expected
|
2019-12-01 20:43:19 +01:00
|
|
|
|
|
|
|
it "embeds inline fragments without type" $ do
|
2020-05-14 09:17:14 +02:00
|
|
|
let sourceQuery = [r|{
|
2019-12-01 20:43:19 +01:00
|
|
|
garment {
|
|
|
|
circumference
|
|
|
|
... {
|
|
|
|
size
|
|
|
|
}
|
|
|
|
}
|
|
|
|
}|]
|
2020-05-27 23:18:35 +02:00
|
|
|
resolvers = ("garment", Object $ HashMap.fromList [circumference, size])
|
2019-12-01 20:43:19 +01:00
|
|
|
|
2020-05-27 23:18:35 +02:00
|
|
|
actual <- graphql (toSchema "garment" resolvers) sourceQuery
|
2020-07-19 07:36:06 +02:00
|
|
|
let expected = HashMap.singleton "data"
|
|
|
|
$ Aeson.object
|
|
|
|
[ "garment" .= Aeson.object
|
2019-12-01 20:43:19 +01:00
|
|
|
[ "circumference" .= (60 :: Int)
|
|
|
|
, "size" .= ("L" :: Text)
|
|
|
|
]
|
2019-10-07 21:03:07 +02:00
|
|
|
]
|
2020-07-19 07:36:06 +02:00
|
|
|
in actual `shouldResolveTo` expected
|
2019-12-01 20:43:19 +01:00
|
|
|
|
|
|
|
it "evaluates fragments on Query" $ do
|
2020-05-14 09:17:14 +02:00
|
|
|
let sourceQuery = [r|{
|
2019-12-01 20:43:19 +01:00
|
|
|
... {
|
|
|
|
size
|
|
|
|
}
|
|
|
|
}|]
|
2020-07-19 07:36:06 +02:00
|
|
|
in graphql (toSchema "size" size) `shouldResolve` sourceQuery
|
2019-12-01 20:43:19 +01:00
|
|
|
|
|
|
|
describe "Fragment spread executor" $ do
|
|
|
|
it "evaluates fragment spreads" $ do
|
2020-05-14 09:17:14 +02:00
|
|
|
let sourceQuery = [r|
|
2019-12-01 20:43:19 +01:00
|
|
|
{
|
|
|
|
...circumferenceFragment
|
|
|
|
}
|
|
|
|
|
|
|
|
fragment circumferenceFragment on Hat {
|
|
|
|
circumference
|
|
|
|
}
|
|
|
|
|]
|
|
|
|
|
2020-05-27 23:18:35 +02:00
|
|
|
actual <- graphql (toSchema "circumference" circumference) sourceQuery
|
2020-07-19 07:36:06 +02:00
|
|
|
let expected = HashMap.singleton "data"
|
|
|
|
$ Aeson.object
|
2019-10-11 23:28:55 +02:00
|
|
|
[ "circumference" .= (60 :: Int)
|
|
|
|
]
|
2020-07-19 07:36:06 +02:00
|
|
|
in actual `shouldResolveTo` expected
|
2019-12-01 20:43:19 +01:00
|
|
|
|
|
|
|
it "evaluates nested fragments" $ do
|
2020-05-14 09:17:14 +02:00
|
|
|
let sourceQuery = [r|
|
2019-12-01 20:43:19 +01:00
|
|
|
{
|
|
|
|
garment {
|
|
|
|
...circumferenceFragment
|
|
|
|
}
|
|
|
|
}
|
|
|
|
|
|
|
|
fragment circumferenceFragment on Hat {
|
|
|
|
...hatFragment
|
|
|
|
}
|
|
|
|
|
|
|
|
fragment hatFragment on Hat {
|
|
|
|
circumference
|
|
|
|
}
|
|
|
|
|]
|
|
|
|
|
2020-05-27 23:18:35 +02:00
|
|
|
actual <- graphql (toSchema "Hat" $ garment "Hat") sourceQuery
|
2020-07-19 07:36:06 +02:00
|
|
|
let expected = HashMap.singleton "data"
|
|
|
|
$ Aeson.object
|
|
|
|
[ "garment" .= Aeson.object
|
2019-12-01 20:43:19 +01:00
|
|
|
[ "circumference" .= (60 :: Int)
|
|
|
|
]
|
|
|
|
]
|
2020-07-19 07:36:06 +02:00
|
|
|
in actual `shouldResolveTo` expected
|
2019-12-01 20:43:19 +01:00
|
|
|
|
|
|
|
it "rejects recursive fragments" $ do
|
2020-07-19 07:36:06 +02:00
|
|
|
let expected = HashMap.singleton "data" $ Aeson.object []
|
2020-05-23 06:46:21 +02:00
|
|
|
sourceQuery = [r|
|
2019-12-01 20:43:19 +01:00
|
|
|
{
|
|
|
|
...circumferenceFragment
|
|
|
|
}
|
|
|
|
|
|
|
|
fragment circumferenceFragment on Hat {
|
|
|
|
...circumferenceFragment
|
|
|
|
}
|
|
|
|
|]
|
|
|
|
|
2020-05-27 23:18:35 +02:00
|
|
|
actual <- graphql (toSchema "circumference" circumference) sourceQuery
|
2020-07-19 07:36:06 +02:00
|
|
|
actual `shouldResolveTo` expected
|
2019-12-01 20:43:19 +01:00
|
|
|
|
|
|
|
it "considers type condition" $ do
|
2020-05-14 09:17:14 +02:00
|
|
|
let sourceQuery = [r|
|
2019-12-01 20:43:19 +01:00
|
|
|
{
|
|
|
|
garment {
|
|
|
|
...circumferenceFragment
|
|
|
|
...sizeFragment
|
|
|
|
}
|
|
|
|
}
|
|
|
|
fragment circumferenceFragment on Hat {
|
|
|
|
circumference
|
|
|
|
}
|
|
|
|
fragment sizeFragment on Shirt {
|
|
|
|
size
|
|
|
|
}
|
|
|
|
|]
|
2020-07-19 07:36:06 +02:00
|
|
|
expected = HashMap.singleton "data"
|
|
|
|
$ Aeson.object
|
|
|
|
[ "garment" .= Aeson.object
|
2019-12-01 20:43:19 +01:00
|
|
|
[ "circumference" .= (60 :: Int)
|
|
|
|
]
|
|
|
|
]
|
2020-05-27 23:18:35 +02:00
|
|
|
actual <- graphql (toSchema "Hat" $ garment "Hat") sourceQuery
|
2020-07-19 07:36:06 +02:00
|
|
|
actual `shouldResolveTo` expected
|