graphql/tests/Language/GraphQL/Execute/CoerceSpec.hs

53 lines
2.0 KiB
Haskell
Raw Normal View History

{- 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/. -}
2020-05-21 10:20:59 +02:00
{-# LANGUAGE OverloadedStrings #-}
module Language.GraphQL.Execute.CoerceSpec
( spec
) where
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe (isNothing)
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
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-06-13 07:20:19 +02:00
namedIdType :: In.Type
namedIdType = In.NamedScalarType id
2020-05-21 10:20:59 +02:00
spec :: Spec
2021-12-24 13:35:18 +01:00
spec =
2020-06-19 10:53:41 +02:00
describe "coerceInputLiteral" $ do
2020-05-22 10:11:48 +02:00
it "coerces enums" $
let expected = Just (Enum "NORTH")
2020-06-13 07:20:19 +02:00
actual = Coerce.coerceInputLiteral
(In.NamedEnumType direction) (Enum "NORTH")
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
(In.NamedEnumType direction) (Enum "NORTH_EAST")
2020-05-22 10:11:48 +02:00
in actual `shouldSatisfy` isNothing
it "coerces integers to IDs" $
let expected = Just (String "1234")
2020-06-13 07:20:19 +02:00
actual = Coerce.coerceInputLiteral namedIdType (Int 1234)
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