Check point

This commit is contained in:
2020-05-24 13:51:00 +02:00
parent 7cd4821718
commit eb90a4091c
18 changed files with 281 additions and 271 deletions

View File

@ -15,6 +15,7 @@ import Language.GraphQL.AST.Core
import Language.GraphQL.Execute.Coerce
import Language.GraphQL.Schema
import Language.GraphQL.Type.Definition
import qualified Language.GraphQL.Type.In as In
import Prelude hiding (id)
import Test.Hspec (Spec, describe, it, shouldBe, shouldSatisfy)
@ -22,12 +23,12 @@ direction :: EnumType
direction = EnumType "Direction" Nothing
$ Set.fromList ["NORTH", "EAST", "SOUTH", "WEST"]
coerceInputLiteral :: InputType -> Value -> Maybe Subs
coerceInputLiteral :: InputType -> In.Value -> Maybe Subs
coerceInputLiteral input value = coerceInputLiterals
(HashMap.singleton "variableName" input)
(HashMap.singleton "variableName" value)
lookupActual :: Maybe (HashMap Name Value) -> Maybe Value
lookupActual :: Maybe (HashMap Name In.Value) -> Maybe In.Value
lookupActual = (HashMap.lookup "variableName" =<<)
singletonInputObject :: InputType
@ -41,22 +42,22 @@ spec :: Spec
spec = do
describe "ToGraphQL Aeson" $ do
it "coerces strings" $
let expected = Just (String "asdf")
let expected = Just (In.String "asdf")
actual = coerceVariableValue
(ScalarInputType string) (Aeson.String "asdf")
in actual `shouldBe` expected
it "coerces non-null strings" $
let expected = Just (String "asdf")
let expected = Just (In.String "asdf")
actual = coerceVariableValue
(NonNullScalarInputType string) (Aeson.String "asdf")
in actual `shouldBe` expected
it "coerces booleans" $
let expected = Just (Boolean True)
let expected = Just (In.Boolean True)
actual = coerceVariableValue
(ScalarInputType boolean) (Aeson.Bool True)
in actual `shouldBe` expected
it "coerces zero to an integer" $
let expected = Just (Int 0)
let expected = Just (In.Int 0)
actual = coerceVariableValue
(ScalarInputType int) (Aeson.Number 0)
in actual `shouldBe` expected
@ -65,24 +66,24 @@ spec = do
(ScalarInputType int) (Aeson.Number $ scientific 14 (-1))
in actual `shouldSatisfy` isNothing
it "coerces float numbers" $
let expected = Just (Float 1.4)
let expected = Just (In.Float 1.4)
actual = coerceVariableValue
(ScalarInputType float) (Aeson.Number $ scientific 14 (-1))
in actual `shouldBe` expected
it "coerces IDs" $
let expected = Just (String "1234")
let expected = Just (In.String "1234")
actual = coerceVariableValue
(ScalarInputType id) (Aeson.String "1234")
in actual `shouldBe` expected
it "coerces input objects" $
let actual = coerceVariableValue singletonInputObject
$ Aeson.object ["field" .= ("asdf" :: Aeson.Value)]
expected = Just $ Object $ HashMap.singleton "field" "asdf"
expected = Just $ In.Object $ HashMap.singleton "field" "asdf"
in actual `shouldBe` expected
it "skips the field if it is missing in the variables" $
let actual = coerceVariableValue
singletonInputObject Aeson.emptyObject
expected = Just $ Object HashMap.empty
expected = Just $ In.Object HashMap.empty
in actual `shouldBe` expected
it "fails if input object value contains extra fields" $
let actual = coerceVariableValue singletonInputObject
@ -94,25 +95,25 @@ spec = do
in actual `shouldSatisfy` isNothing
it "preserves null" $
let actual = coerceVariableValue (ScalarInputType id) Aeson.Null
in actual `shouldBe` Just Null
in actual `shouldBe` Just In.Null
it "preserves list order" $
let list = Aeson.toJSONList ["asdf" :: Aeson.Value, "qwer"]
listType = (ListInputType $ ScalarInputType string)
actual = coerceVariableValue listType list
expected = Just $ List [String "asdf", String "qwer"]
expected = Just $ In.List [In.String "asdf", In.String "qwer"]
in actual `shouldBe` expected
describe "coerceInputLiterals" $ do
it "coerces enums" $
let expected = Just (Enum "NORTH")
let expected = Just (In.Enum "NORTH")
actual = coerceInputLiteral
(EnumInputType direction) (Enum "NORTH")
(EnumInputType direction) (In.Enum "NORTH")
in lookupActual actual `shouldBe` expected
it "fails with non-existing enum value" $
let actual = coerceInputLiteral
(EnumInputType direction) (Enum "NORTH_EAST")
(EnumInputType direction) (In.Enum "NORTH_EAST")
in actual `shouldSatisfy` isNothing
it "coerces integers to IDs" $
let expected = Just (String "1234")
actual = coerceInputLiteral (ScalarInputType id) (Int 1234)
let expected = Just (In.String "1234")
actual = coerceInputLiteral (ScalarInputType id) (In.Int 1234)
in lookupActual actual `shouldBe` expected

View File

@ -10,16 +10,15 @@ import qualified Data.Sequence as Sequence
import Language.GraphQL.AST.Core
import Language.GraphQL.Error
import Language.GraphQL.Schema
import qualified Language.GraphQL.Type as Type
import Language.GraphQL.Type.Definition
import qualified Language.GraphQL.Type.Out as Out
import Test.Hspec (Spec, describe, it, shouldBe)
spec :: Spec
spec =
describe "resolve" $
it "ignores invalid __typename" $ do
let resolver = NestingResolver $ pure $ object
[ wrappedObject "field" $ pure $ Type.S "T"
let resolver = pure $ object
[ Resolver "field" $ pure $ Out.String "T"
]
schema = HashMap.singleton "__typename" resolver
fields = Sequence.singleton

View File

@ -0,0 +1,15 @@
{-# LANGUAGE OverloadedStrings #-}
module Language.GraphQL.Type.OutSpec
( spec
) where
import Data.Functor.Identity (Identity)
import qualified Language.GraphQL.Type.Out as Out
import Test.Hspec (Spec, describe, it, shouldBe)
spec :: Spec
spec =
describe "Value" $
it "supports overloaded strings" $
let string = "Goldstaub abblasen." :: (Out.Value Identity)
in string `shouldBe` Out.String "Goldstaub abblasen."

View File

@ -8,6 +8,7 @@ import Data.Aeson (Value(..), object, (.=))
import qualified Data.HashMap.Strict as HashMap
import Language.GraphQL
import Language.GraphQL.Type.Definition
import qualified Language.GraphQL.Type.Out as Out
import Language.GraphQL.Type.Schema (Schema(..))
import Test.Hspec (Spec, describe, it, shouldBe)
import Text.RawString.QQ (r)
@ -15,7 +16,7 @@ import Text.RawString.QQ (r)
experimentalResolver :: Schema IO
experimentalResolver = Schema { query = queryType, mutation = Nothing }
where
resolver = ValueResolver $ pure $ Number 5
resolver = pure $ Out.Int 5
queryType = ObjectType "Query" Nothing
$ HashMap.singleton "experimentalField"
$ Field Nothing (ScalarOutputType int) mempty resolver

View File

@ -9,7 +9,9 @@ import qualified Data.HashMap.Strict as HashMap
import Data.Text (Text)
import Language.GraphQL
import qualified Language.GraphQL.Schema as Schema
import qualified Language.GraphQL.Type as Type
import Language.GraphQL.Type.Definition
import qualified Language.GraphQL.Type.Out as Out
import Language.GraphQL.Type.Schema
import Test.Hspec
( Spec
, describe
@ -17,21 +19,19 @@ import Test.Hspec
, shouldBe
, shouldNotSatisfy
)
import Language.GraphQL.Type.Definition
import Language.GraphQL.Type.Schema
import Text.RawString.QQ (r)
size :: Schema.Resolver IO
size = Schema.wrappedObject "size" $ pure $ Type.S "L"
size = Schema.Resolver "size" $ pure $ Out.String "L"
circumference :: Schema.Resolver IO
circumference = Schema.wrappedObject "circumference" $ pure $ Type.I 60
circumference = Schema.Resolver "circumference" $ pure $ Out.Int 60
garment :: Text -> Schema.Resolver IO
garment typeName = Schema.wrappedObject "garment"
garment typeName = Schema.Resolver "garment"
$ pure $ Schema.object
[ if typeName == "Hat" then circumference else size
, Schema.wrappedObject "__typename" $ pure $ Type.S typeName
, Schema.Resolver "__typename" $ pure $ Out.String typeName
]
inlineQuery :: Text
@ -107,7 +107,7 @@ spec = do
}
}
}|]
resolvers = Schema.wrappedObject "garment"
resolvers = Schema.Resolver "garment"
$ pure $ Schema.object [circumference, size]
actual <- graphql (toSchema resolvers) sourceQuery

View File

@ -11,8 +11,8 @@ import qualified Language.GraphQL.Schema as Schema
import Test.Hspec (Spec, describe, it, shouldBe)
import Text.RawString.QQ (r)
import Language.GraphQL.Type.Definition
import qualified Language.GraphQL.Type.Out as Out
import Language.GraphQL.Type.Schema
import qualified Language.GraphQL.Type as Type
hatType :: ObjectType IO
hatType = ObjectType "Hat" Nothing
@ -20,20 +20,19 @@ hatType = ObjectType "Hat" Nothing
$ Field Nothing (ScalarOutputType int) mempty resolve
where
(Schema.Resolver resolverName resolve) =
Schema.wrappedObject "circumference" $ pure $ Type.I 60
Schema.Resolver "circumference" $ pure $ Out.Int 60
schema :: Schema IO
schema = Schema
(ObjectType "Query" Nothing hatField)
(Just $ ObjectType "Mutation" Nothing incrementField)
where
garment = NestingResolver
$ pure $ Schema.object
[ Schema.wrappedObject "circumference" $ pure $ Type.I 60
garment = pure $ Schema.object
[ Schema.Resolver "circumference" $ pure $ Out.Int 60
]
incrementField = HashMap.singleton "incrementCircumference"
$ Field Nothing (ScalarOutputType int) mempty
$ NestingResolver $ pure $ Type.I 61
$ pure $ Out.Int 61
hatField = HashMap.singleton "garment"
$ Field Nothing (ObjectOutputType hatType) mempty garment

View File

@ -15,7 +15,8 @@ import Data.Maybe (catMaybes)
import qualified Language.GraphQL.Schema as Schema
import Language.GraphQL.Trans
import Language.GraphQL.Type.Definition
import qualified Language.GraphQL.Type as Type
import qualified Language.GraphQL.Type.In as In
import qualified Language.GraphQL.Type.Out as Out
import Language.GraphQL.Type.Schema
import Test.StarWars.Data
@ -30,45 +31,45 @@ schema = Schema { query = queryType, mutation = Nothing }
, ("droid", Field Nothing (ScalarOutputType string) mempty droid)
]
hero :: FieldResolver Identity
hero = NestingResolver $ do
hero :: ActionT Identity (Out.Value Identity)
hero = do
episode <- argument "episode"
pure $ character $ case episode of
Schema.Enum "NEWHOPE" -> getHero 4
Schema.Enum "EMPIRE" -> getHero 5
Schema.Enum "JEDI" -> getHero 6
In.Enum "NEWHOPE" -> getHero 4
In.Enum "EMPIRE" -> getHero 5
In.Enum "JEDI" -> getHero 6
_ -> artoo
human :: FieldResolver Identity
human = NestingResolver $ do
human :: ActionT Identity (Out.Value Identity)
human = do
id' <- argument "id"
case id' of
Schema.String i -> do
In.String i -> do
humanCharacter <- lift $ return $ getHuman i >>= Just
case humanCharacter of
Nothing -> pure Type.Null
Nothing -> pure Out.Null
Just e -> pure $ character e
_ -> ActionT $ throwE "Invalid arguments."
droid :: FieldResolver Identity
droid = NestingResolver $ do
droid :: ActionT Identity (Out.Value Identity)
droid = do
id' <- argument "id"
case id' of
Schema.String i -> getDroid i >>= pure . character
In.String i -> getDroid i >>= pure . character
_ -> ActionT $ throwE "Invalid arguments."
character :: Character -> Type.Wrapping (FieldResolver Identity)
character :: Character -> Out.Value Identity
character char = Schema.object
[ Schema.wrappedObject "id" $ pure $ Type.S $ id_ char
, Schema.wrappedObject "name" $ pure $ Type.S $ name_ char
, Schema.wrappedObject "friends"
$ pure
$ Type.List
$ fmap character
$ getFriends char
, Schema.wrappedObject "appearsIn" $ pure
$ Type.List $ Type.E <$> catMaybes (getEpisode <$> appearsIn char)
, Schema.wrappedObject "secretBackstory" $ Type.S <$> secretBackstory char
, Schema.wrappedObject "homePlanet" $ pure $ Type.S $ either mempty homePlanet char
, Schema.wrappedObject "__typename" $ pure $ Type.S $ typeName char
[ Schema.Resolver "id" $ pure $ Out.String $ id_ char
, Schema.Resolver "name" $ pure $ Out.String $ name_ char
, Schema.Resolver "friends"
$ pure $ Out.List $ fmap character $ getFriends char
, Schema.Resolver "appearsIn" $ pure
$ Out.List $ Out.Enum <$> catMaybes (getEpisode <$> appearsIn char)
, Schema.Resolver "secretBackstory" $ Out.String
<$> secretBackstory char
, Schema.Resolver "homePlanet" $ pure $ Out.String
$ either mempty homePlanet char
, Schema.Resolver "__typename" $ pure $ Out.String
$ typeName char
]