@ -9,7 +9,7 @@ import qualified Data.Aeson.Types as Aeson
|
||||
import qualified Data.HashMap.Strict as HashMap
|
||||
import Data.Maybe (isNothing)
|
||||
import Data.Scientific (scientific)
|
||||
import Language.GraphQL.Execute.Coerce
|
||||
import qualified Language.GraphQL.Execute.Coerce as Coerce
|
||||
import Language.GraphQL.Type.Definition
|
||||
import qualified Language.GraphQL.Type.In as In
|
||||
import Prelude hiding (id)
|
||||
@ -30,55 +30,58 @@ singletonInputObject = In.NamedInputObjectType type'
|
||||
inputFields = HashMap.singleton "field" field
|
||||
field = In.InputField Nothing (In.NamedScalarType string) Nothing
|
||||
|
||||
namedIdType :: In.Type
|
||||
namedIdType = In.NamedScalarType id
|
||||
|
||||
spec :: Spec
|
||||
spec = do
|
||||
describe "VariableValue Aeson" $ do
|
||||
it "coerces strings" $
|
||||
let expected = Just (String "asdf")
|
||||
actual = coerceVariableValue
|
||||
actual = Coerce.coerceVariableValue
|
||||
(In.NamedScalarType string) (Aeson.String "asdf")
|
||||
in actual `shouldBe` expected
|
||||
it "coerces non-null strings" $
|
||||
let expected = Just (String "asdf")
|
||||
actual = coerceVariableValue
|
||||
actual = Coerce.coerceVariableValue
|
||||
(In.NonNullScalarType string) (Aeson.String "asdf")
|
||||
in actual `shouldBe` expected
|
||||
it "coerces booleans" $
|
||||
let expected = Just (Boolean True)
|
||||
actual = coerceVariableValue
|
||||
actual = Coerce.coerceVariableValue
|
||||
(In.NamedScalarType boolean) (Aeson.Bool True)
|
||||
in actual `shouldBe` expected
|
||||
it "coerces zero to an integer" $
|
||||
let expected = Just (Int 0)
|
||||
actual = coerceVariableValue
|
||||
actual = Coerce.coerceVariableValue
|
||||
(In.NamedScalarType int) (Aeson.Number 0)
|
||||
in actual `shouldBe` expected
|
||||
it "rejects fractional if an integer is expected" $
|
||||
let actual = coerceVariableValue
|
||||
let actual = Coerce.coerceVariableValue
|
||||
(In.NamedScalarType int) (Aeson.Number $ scientific 14 (-1))
|
||||
in actual `shouldSatisfy` isNothing
|
||||
it "coerces float numbers" $
|
||||
let expected = Just (Float 1.4)
|
||||
actual = coerceVariableValue
|
||||
actual = Coerce.coerceVariableValue
|
||||
(In.NamedScalarType float) (Aeson.Number $ scientific 14 (-1))
|
||||
in actual `shouldBe` expected
|
||||
it "coerces IDs" $
|
||||
let expected = Just (String "1234")
|
||||
actual = coerceVariableValue
|
||||
(In.NamedScalarType id) (Aeson.String "1234")
|
||||
json = Aeson.String "1234"
|
||||
actual = Coerce.coerceVariableValue namedIdType json
|
||||
in actual `shouldBe` expected
|
||||
it "coerces input objects" $
|
||||
let actual = coerceVariableValue singletonInputObject
|
||||
let actual = Coerce.coerceVariableValue singletonInputObject
|
||||
$ Aeson.object ["field" .= ("asdf" :: Aeson.Value)]
|
||||
expected = Just $ Object $ HashMap.singleton "field" "asdf"
|
||||
in actual `shouldBe` expected
|
||||
it "skips the field if it is missing in the variables" $
|
||||
let actual = coerceVariableValue
|
||||
let actual = Coerce.coerceVariableValue
|
||||
singletonInputObject Aeson.emptyObject
|
||||
expected = Just $ Object HashMap.empty
|
||||
in actual `shouldBe` expected
|
||||
it "fails if input object value contains extra fields" $
|
||||
let actual = coerceVariableValue singletonInputObject
|
||||
let actual = Coerce.coerceVariableValue singletonInputObject
|
||||
$ Aeson.object variableFields
|
||||
variableFields =
|
||||
[ "field" .= ("asdf" :: Aeson.Value)
|
||||
@ -86,26 +89,26 @@ spec = do
|
||||
]
|
||||
in actual `shouldSatisfy` isNothing
|
||||
it "preserves null" $
|
||||
let actual = coerceVariableValue (In.NamedScalarType id) Aeson.Null
|
||||
let actual = Coerce.coerceVariableValue namedIdType Aeson.Null
|
||||
in actual `shouldBe` Just Null
|
||||
it "preserves list order" $
|
||||
let list = Aeson.toJSONList ["asdf" :: Aeson.Value, "qwer"]
|
||||
listType = (In.ListType $ In.NamedScalarType string)
|
||||
actual = coerceVariableValue listType list
|
||||
actual = Coerce.coerceVariableValue listType list
|
||||
expected = Just $ List [String "asdf", String "qwer"]
|
||||
in actual `shouldBe` expected
|
||||
|
||||
describe "coerceInputLiterals" $ do
|
||||
it "coerces enums" $
|
||||
let expected = Just (Enum "NORTH")
|
||||
actual = coerceInputLiteral
|
||||
actual = Coerce.coerceInputLiteral
|
||||
(In.NamedEnumType direction) (Enum "NORTH")
|
||||
in actual `shouldBe` expected
|
||||
it "fails with non-existing enum value" $
|
||||
let actual = coerceInputLiteral
|
||||
let actual = Coerce.coerceInputLiteral
|
||||
(In.NamedEnumType direction) (Enum "NORTH_EAST")
|
||||
in actual `shouldSatisfy` isNothing
|
||||
it "coerces integers to IDs" $
|
||||
let expected = Just (String "1234")
|
||||
actual = coerceInputLiteral (In.NamedScalarType id) (Int 1234)
|
||||
actual = Coerce.coerceInputLiteral namedIdType (Int 1234)
|
||||
in actual `shouldBe` expected
|
||||
|
@ -12,7 +12,7 @@ import Language.GraphQL.AST (Name)
|
||||
import Language.GraphQL.AST.Parser (document)
|
||||
import Language.GraphQL.Error
|
||||
import Language.GraphQL.Execute
|
||||
import Language.GraphQL.Type
|
||||
import Language.GraphQL.Type as Type
|
||||
import Language.GraphQL.Type.Out as Out
|
||||
import Test.Hspec (Spec, describe, it, shouldBe)
|
||||
import Text.Megaparsec (parse)
|
||||
@ -25,7 +25,7 @@ queryType = Out.ObjectType "Query" Nothing []
|
||||
$ HashMap.singleton "philosopher"
|
||||
$ Out.Resolver philosopherField
|
||||
$ pure
|
||||
$ Object mempty
|
||||
$ Type.Object mempty
|
||||
where
|
||||
philosopherField =
|
||||
Out.Field Nothing (Out.NonNullObjectType philosopherType) HashMap.empty
|
||||
@ -38,8 +38,8 @@ philosopherType = Out.ObjectType "Philosopher" Nothing []
|
||||
[ ("firstName", firstNameResolver)
|
||||
, ("lastName", lastNameResolver)
|
||||
]
|
||||
firstNameResolver = Out.Resolver firstNameField $ pure $ String "Friedrich"
|
||||
lastNameResolver = Out.Resolver lastNameField $ pure $ String "Nietzsche"
|
||||
firstNameResolver = Out.Resolver firstNameField $ pure $ Type.String "Friedrich"
|
||||
lastNameResolver = Out.Resolver lastNameField $ pure $ Type.String "Nietzsche"
|
||||
firstNameField = Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
|
||||
lastNameField = Out.Field Nothing (Out.NonNullScalarType string) HashMap.empty
|
||||
|
||||
|
Reference in New Issue
Block a user