2020-05-21 10:20:59 +02:00
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
module Language.GraphQL.Execute.CoerceSpec
|
|
|
|
( spec
|
|
|
|
) where
|
|
|
|
|
|
|
|
import Data.Aeson as Aeson ((.=))
|
|
|
|
import qualified Data.Aeson as Aeson
|
|
|
|
import qualified Data.Aeson.Types as Aeson
|
|
|
|
import qualified Data.HashMap.Strict as HashMap
|
|
|
|
import Data.Maybe (isNothing)
|
|
|
|
import Data.Scientific (scientific)
|
2020-06-13 07:20:19 +02:00
|
|
|
import qualified Language.GraphQL.Execute.Coerce as Coerce
|
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.In as In
|
2020-05-21 10:20:59 +02:00
|
|
|
import Prelude hiding (id)
|
|
|
|
import Test.Hspec (Spec, describe, it, shouldBe, shouldSatisfy)
|
|
|
|
|
2020-05-22 10:11:48 +02:00
|
|
|
direction :: EnumType
|
2020-06-07 06:16:45 +02:00
|
|
|
direction = EnumType "Direction" Nothing $ HashMap.fromList
|
|
|
|
[ ("NORTH", EnumValue Nothing)
|
|
|
|
, ("EAST", EnumValue Nothing)
|
|
|
|
, ("SOUTH", EnumValue Nothing)
|
|
|
|
, ("WEST", EnumValue Nothing)
|
|
|
|
]
|
2020-05-22 10:11:48 +02:00
|
|
|
|
2020-05-25 07:41:21 +02:00
|
|
|
singletonInputObject :: In.Type
|
|
|
|
singletonInputObject = In.NamedInputObjectType type'
|
2020-05-21 10:20:59 +02:00
|
|
|
where
|
2020-05-25 07:41:21 +02:00
|
|
|
type' = In.InputObjectType "ObjectName" Nothing inputFields
|
2020-05-21 10:20:59 +02:00
|
|
|
inputFields = HashMap.singleton "field" field
|
2020-05-25 07:41:21 +02:00
|
|
|
field = In.InputField Nothing (In.NamedScalarType string) Nothing
|
2020-05-21 10:20:59 +02:00
|
|
|
|
2020-06-13 07:20:19 +02:00
|
|
|
namedIdType :: In.Type
|
|
|
|
namedIdType = In.NamedScalarType id
|
|
|
|
|
2020-05-21 10:20:59 +02:00
|
|
|
spec :: Spec
|
2020-05-22 10:11:48 +02:00
|
|
|
spec = do
|
2020-06-06 21:22:11 +02:00
|
|
|
describe "VariableValue Aeson" $ do
|
2020-05-21 10:20:59 +02:00
|
|
|
it "coerces strings" $
|
2020-05-27 23:18:35 +02:00
|
|
|
let expected = Just (String "asdf")
|
2020-06-13 07:20:19 +02:00
|
|
|
actual = Coerce.coerceVariableValue
|
2020-05-25 07:41:21 +02:00
|
|
|
(In.NamedScalarType string) (Aeson.String "asdf")
|
2020-05-21 10:20:59 +02:00
|
|
|
in actual `shouldBe` expected
|
|
|
|
it "coerces non-null strings" $
|
2020-05-27 23:18:35 +02:00
|
|
|
let expected = Just (String "asdf")
|
2020-06-13 07:20:19 +02:00
|
|
|
actual = Coerce.coerceVariableValue
|
2020-05-25 07:41:21 +02:00
|
|
|
(In.NonNullScalarType string) (Aeson.String "asdf")
|
2020-05-21 10:20:59 +02:00
|
|
|
in actual `shouldBe` expected
|
|
|
|
it "coerces booleans" $
|
2020-05-27 23:18:35 +02:00
|
|
|
let expected = Just (Boolean True)
|
2020-06-13 07:20:19 +02:00
|
|
|
actual = Coerce.coerceVariableValue
|
2020-05-25 07:41:21 +02:00
|
|
|
(In.NamedScalarType boolean) (Aeson.Bool True)
|
2020-05-21 10:20:59 +02:00
|
|
|
in actual `shouldBe` expected
|
|
|
|
it "coerces zero to an integer" $
|
2020-05-27 23:18:35 +02:00
|
|
|
let expected = Just (Int 0)
|
2020-06-13 07:20:19 +02:00
|
|
|
actual = Coerce.coerceVariableValue
|
2020-05-25 07:41:21 +02:00
|
|
|
(In.NamedScalarType int) (Aeson.Number 0)
|
2020-05-21 10:20:59 +02:00
|
|
|
in actual `shouldBe` expected
|
|
|
|
it "rejects fractional if an integer is expected" $
|
2020-06-13 07:20:19 +02:00
|
|
|
let actual = Coerce.coerceVariableValue
|
2020-05-25 07:41:21 +02:00
|
|
|
(In.NamedScalarType int) (Aeson.Number $ scientific 14 (-1))
|
2020-05-21 10:20:59 +02:00
|
|
|
in actual `shouldSatisfy` isNothing
|
|
|
|
it "coerces float numbers" $
|
2020-05-27 23:18:35 +02:00
|
|
|
let expected = Just (Float 1.4)
|
2020-06-13 07:20:19 +02:00
|
|
|
actual = Coerce.coerceVariableValue
|
2020-05-25 07:41:21 +02:00
|
|
|
(In.NamedScalarType float) (Aeson.Number $ scientific 14 (-1))
|
2020-05-21 10:20:59 +02:00
|
|
|
in actual `shouldBe` expected
|
|
|
|
it "coerces IDs" $
|
2020-05-27 23:18:35 +02:00
|
|
|
let expected = Just (String "1234")
|
2020-06-13 07:20:19 +02:00
|
|
|
json = Aeson.String "1234"
|
|
|
|
actual = Coerce.coerceVariableValue namedIdType json
|
2020-05-21 10:20:59 +02:00
|
|
|
in actual `shouldBe` expected
|
|
|
|
it "coerces input objects" $
|
2020-06-13 07:20:19 +02:00
|
|
|
let actual = Coerce.coerceVariableValue singletonInputObject
|
2020-05-21 10:20:59 +02:00
|
|
|
$ Aeson.object ["field" .= ("asdf" :: Aeson.Value)]
|
2020-05-27 23:18:35 +02:00
|
|
|
expected = Just $ Object $ HashMap.singleton "field" "asdf"
|
2020-05-21 10:20:59 +02:00
|
|
|
in actual `shouldBe` expected
|
|
|
|
it "skips the field if it is missing in the variables" $
|
2020-06-13 07:20:19 +02:00
|
|
|
let actual = Coerce.coerceVariableValue
|
2020-05-21 10:20:59 +02:00
|
|
|
singletonInputObject Aeson.emptyObject
|
2020-05-27 23:18:35 +02:00
|
|
|
expected = Just $ Object HashMap.empty
|
2020-05-21 10:20:59 +02:00
|
|
|
in actual `shouldBe` expected
|
|
|
|
it "fails if input object value contains extra fields" $
|
2020-06-13 07:20:19 +02:00
|
|
|
let actual = Coerce.coerceVariableValue singletonInputObject
|
2020-05-21 10:20:59 +02:00
|
|
|
$ Aeson.object variableFields
|
|
|
|
variableFields =
|
|
|
|
[ "field" .= ("asdf" :: Aeson.Value)
|
|
|
|
, "extra" .= ("qwer" :: Aeson.Value)
|
|
|
|
]
|
|
|
|
in actual `shouldSatisfy` isNothing
|
|
|
|
it "preserves null" $
|
2020-06-13 07:20:19 +02:00
|
|
|
let actual = Coerce.coerceVariableValue namedIdType Aeson.Null
|
2020-05-27 23:18:35 +02:00
|
|
|
in actual `shouldBe` Just Null
|
2020-05-21 10:20:59 +02:00
|
|
|
it "preserves list order" $
|
|
|
|
let list = Aeson.toJSONList ["asdf" :: Aeson.Value, "qwer"]
|
2020-05-25 07:41:21 +02:00
|
|
|
listType = (In.ListType $ In.NamedScalarType string)
|
2020-06-13 07:20:19 +02:00
|
|
|
actual = Coerce.coerceVariableValue listType list
|
2020-05-27 23:18:35 +02:00
|
|
|
expected = Just $ List [String "asdf", String "qwer"]
|
2020-05-21 10:20:59 +02:00
|
|
|
in actual `shouldBe` expected
|
2020-05-22 10:11:48 +02:00
|
|
|
|
2020-06-19 10:53:41 +02:00
|
|
|
describe "coerceInputLiteral" $ do
|
2020-05-22 10:11:48 +02:00
|
|
|
it "coerces enums" $
|
2020-05-27 23:18:35 +02:00
|
|
|
let expected = Just (Enum "NORTH")
|
2020-06-13 07:20:19 +02:00
|
|
|
actual = Coerce.coerceInputLiteral
|
2020-05-27 23:18:35 +02:00
|
|
|
(In.NamedEnumType direction) (Enum "NORTH")
|
2020-06-06 21:22:11 +02:00
|
|
|
in actual `shouldBe` expected
|
2020-05-22 10:11:48 +02:00
|
|
|
it "fails with non-existing enum value" $
|
2020-06-13 07:20:19 +02:00
|
|
|
let actual = Coerce.coerceInputLiteral
|
2020-05-27 23:18:35 +02:00
|
|
|
(In.NamedEnumType direction) (Enum "NORTH_EAST")
|
2020-05-22 10:11:48 +02:00
|
|
|
in actual `shouldSatisfy` isNothing
|
|
|
|
it "coerces integers to IDs" $
|
2020-05-27 23:18:35 +02:00
|
|
|
let expected = Just (String "1234")
|
2020-06-13 07:20:19 +02:00
|
|
|
actual = Coerce.coerceInputLiteral namedIdType (Int 1234)
|
2020-06-06 21:22:11 +02:00
|
|
|
in actual `shouldBe` expected
|
2020-06-19 10:53:41 +02:00
|
|
|
it "coerces nulls" $ do
|
|
|
|
let actual = Coerce.coerceInputLiteral namedIdType Null
|
|
|
|
in actual `shouldBe` Just Null
|
|
|
|
it "wraps singleton lists" $ do
|
|
|
|
let expected = Just $ List [List [String "1"]]
|
|
|
|
embeddedType = In.ListType $ In.ListType namedIdType
|
|
|
|
actual = Coerce.coerceInputLiteral embeddedType (String "1")
|
|
|
|
in actual `shouldBe` expected
|