Put JSON support behind a flag

This commit is contained in:
2021-12-24 13:35:18 +01:00
parent df078a59d0
commit 116aa1f6bb
8 changed files with 136 additions and 159 deletions

View File

@ -7,9 +7,9 @@ module Language.GraphQL.ErrorSpec
( spec
) where
import qualified Data.Aeson as Aeson
import Data.List.NonEmpty (NonEmpty (..))
import Language.GraphQL.Error
import qualified Language.GraphQL.Type as Type
import Test.Hspec
( Spec
, describe
@ -31,6 +31,6 @@ spec = describe "parseError" $
, pstateTabWidth = mkPos 1
, pstateLinePrefix = ""
}
Response Aeson.Null actual <-
Response Type.Null actual <-
parseError (ParseErrorBundle parseErrors posState)
length actual `shouldBe` 1

View File

@ -7,12 +7,8 @@ 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)
import qualified Language.GraphQL.Execute.Coerce as Coerce
import Language.GraphQL.Type
import qualified Language.GraphQL.Type.In as In
@ -27,81 +23,11 @@ direction = EnumType "Direction" Nothing $ HashMap.fromList
, ("WEST", EnumValue Nothing)
]
singletonInputObject :: In.Type
singletonInputObject = In.NamedInputObjectType type'
where
type' = In.InputObjectType "ObjectName" Nothing inputFields
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 = Coerce.coerceVariableValue
(In.NamedScalarType string) (Aeson.String "asdf")
in actual `shouldBe` expected
it "coerces non-null strings" $
let expected = Just (String "asdf")
actual = Coerce.coerceVariableValue
(In.NonNullScalarType string) (Aeson.String "asdf")
in actual `shouldBe` expected
it "coerces booleans" $
let expected = Just (Boolean True)
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 = Coerce.coerceVariableValue
(In.NamedScalarType int) (Aeson.Number 0)
in actual `shouldBe` expected
it "rejects fractional if an integer is expected" $
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 = Coerce.coerceVariableValue
(In.NamedScalarType float) (Aeson.Number $ scientific 14 (-1))
in actual `shouldBe` expected
it "coerces IDs" $
let expected = Just (String "1234")
json = Aeson.String "1234"
actual = Coerce.coerceVariableValue namedIdType json
in actual `shouldBe` expected
it "coerces input objects" $
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 = 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 = Coerce.coerceVariableValue singletonInputObject
$ Aeson.object variableFields
variableFields =
[ "field" .= ("asdf" :: Aeson.Value)
, "extra" .= ("qwer" :: Aeson.Value)
]
in actual `shouldSatisfy` isNothing
it "preserves 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 = Coerce.coerceVariableValue listType list
expected = Just $ List [String "asdf", String "qwer"]
in actual `shouldBe` expected
spec =
describe "coerceInputLiteral" $ do
it "coerces enums" $
let expected = Just (Enum "NORTH")

View File

@ -10,9 +10,6 @@ module Language.GraphQL.ExecuteSpec
import Control.Exception (Exception(..), SomeException)
import Control.Monad.Catch (throwM)
import Data.Aeson ((.=))
import qualified Data.Aeson as Aeson
import Data.Aeson.Types (emptyObject)
import Data.Conduit
import Data.HashMap.Strict (HashMap)
import qualified Data.HashMap.Strict as HashMap
@ -189,12 +186,12 @@ schoolType = EnumType "School" Nothing $ HashMap.fromList
]
type EitherStreamOrValue = Either
(ResponseEventStream (Either SomeException) Aeson.Value)
(Response Aeson.Value)
(ResponseEventStream (Either SomeException) Value)
(Response Value)
execute' :: Document -> Either SomeException EitherStreamOrValue
execute' =
execute philosopherSchema Nothing (mempty :: HashMap Name Aeson.Value)
execute philosopherSchema Nothing (mempty :: HashMap Name Value)
spec :: Spec
spec =
@ -209,38 +206,37 @@ spec =
...cyclicFragment
}
|]
expected = Response emptyObject mempty
expected = Response (Object mempty) mempty
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" sourceQuery
in actual `shouldBe` expected
context "Query" $ do
it "skips unknown fields" $
let data'' = Aeson.object
[ "philosopher" .= Aeson.object
[ "firstName" .= ("Friedrich" :: String)
]
]
let data'' = Object
$ HashMap.singleton "philosopher"
$ Object
$ HashMap.singleton "firstName"
$ String "Friedrich"
expected = Response data'' mempty
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ philosopher { firstName surname } }"
in actual `shouldBe` expected
it "merges selections" $
let data'' = Aeson.object
[ "philosopher" .= Aeson.object
[ "firstName" .= ("Friedrich" :: String)
, "lastName" .= ("Nietzsche" :: String)
let data'' = Object
$ HashMap.singleton "philosopher"
$ Object
$ HashMap.fromList
[ ("firstName", String "Friedrich")
, ("lastName", String "Nietzsche")
]
]
expected = Response data'' mempty
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ philosopher { firstName } philosopher { lastName } }"
in actual `shouldBe` expected
it "errors on invalid output enum values" $
let data'' = Aeson.object
[ "philosopher" .= Aeson.Null
]
let data'' = Object $ HashMap.singleton "philosopher" Null
executionErrors = pure $ Error
{ message =
"Value completion error. Expected type !School, found: EXISTENTIALISM."
@ -253,9 +249,7 @@ spec =
in actual `shouldBe` expected
it "gives location information for non-null unions" $
let data'' = Aeson.object
[ "philosopher" .= Aeson.Null
]
let data'' = Object $ HashMap.singleton "philosopher" Null
executionErrors = pure $ Error
{ message =
"Value completion error. Expected type !Interest, found: { instrument: \"piano\" }."
@ -268,9 +262,7 @@ spec =
in actual `shouldBe` expected
it "gives location information for invalid interfaces" $
let data'' = Aeson.object
[ "philosopher" .= Aeson.Null
]
let data'' = Object $ HashMap.singleton "philosopher" Null
executionErrors = pure $ Error
{ message
= "Value completion error. Expected type !Work, found:\
@ -284,9 +276,7 @@ spec =
in actual `shouldBe` expected
it "gives location information for invalid scalar arguments" $
let data'' = Aeson.object
[ "philosopher" .= Aeson.Null
]
let data'' = Object $ HashMap.singleton "philosopher" Null
executionErrors = pure $ Error
{ message =
"Argument \"id\" has invalid type. Expected type ID, found: True."
@ -299,9 +289,7 @@ spec =
in actual `shouldBe` expected
it "gives location information for failed result coercion" $
let data'' = Aeson.object
[ "philosopher" .= Aeson.Null
]
let data'' = Object $ HashMap.singleton "philosopher" Null
executionErrors = pure $ Error
{ message = "Unable to coerce result to !Int."
, locations = [Location 1 26]
@ -313,9 +301,7 @@ spec =
in actual `shouldBe` expected
it "gives location information for failed result coercion" $
let data'' = Aeson.object
[ "genres" .= Aeson.Null
]
let data'' = Object $ HashMap.singleton "genres" Null
executionErrors = pure $ Error
{ message = "PhilosopherException"
, locations = [Location 1 3]
@ -332,15 +318,13 @@ spec =
, locations = [Location 1 3]
, path = [Segment "count"]
}
expected = Response Aeson.Null executionErrors
expected = Response Null executionErrors
Right (Right actual) = either (pure . parseError) execute'
$ parse document "" "{ count }"
in actual `shouldBe` expected
it "detects nullability errors" $
let data'' = Aeson.object
[ "philosopher" .= Aeson.Null
]
let data'' = Object $ HashMap.singleton "philosopher" Null
executionErrors = pure $ Error
{ message = "Value completion error. Expected type !String, found: null."
, locations = [Location 1 26]
@ -353,11 +337,11 @@ spec =
context "Subscription" $
it "subscribes" $
let data'' = Aeson.object
[ "newQuote" .= Aeson.object
[ "quote" .= ("Naturam expelles furca, tamen usque recurret." :: String)
]
]
let data'' = Object
$ HashMap.singleton "newQuote"
$ Object
$ HashMap.singleton "quote"
$ String "Naturam expelles furca, tamen usque recurret."
expected = Response data'' mempty
Right (Left stream) = either (pure . parseError) execute'
$ parse document "" "subscription { newQuote { quote } }"