graphql/tests/Language/GraphQL/AST/EncoderSpec.hs

270 lines
11 KiB
Haskell
Raw Permalink Normal View History

{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Language.GraphQL.AST.EncoderSpec
( spec
) where
2022-12-25 16:38:00 +01:00
import Data.List.NonEmpty (NonEmpty(..))
2020-09-30 05:14:52 +02:00
import qualified Language.GraphQL.AST.Document as Full
import Language.GraphQL.AST.Encoder
2021-09-23 08:23:38 +02:00
import Language.GraphQL.TH
import Test.Hspec (Spec, context, describe, it, shouldBe, shouldStartWith, shouldEndWith, shouldNotContain)
import Test.QuickCheck (choose, oneof, forAll)
2021-09-23 08:23:38 +02:00
import qualified Data.Text.Lazy as Text.Lazy
spec :: Spec
spec = do
describe "value" $ do
2020-03-31 09:04:34 +02:00
context "null value" $ do
2020-09-30 05:14:52 +02:00
let testNull formatter = value formatter Full.Null `shouldBe` "null"
2020-03-31 09:04:34 +02:00
it "minified" $ testNull minified
it "pretty" $ testNull pretty
context "minified" $ do
it "escapes \\" $
2020-09-30 05:14:52 +02:00
value minified (Full.String "\\") `shouldBe` "\"\\\\\""
it "escapes double quotes" $
2020-09-30 05:14:52 +02:00
value minified (Full.String "\"") `shouldBe` "\"\\\"\""
it "escapes \\f" $
2020-09-30 05:14:52 +02:00
value minified (Full.String "\f") `shouldBe` "\"\\f\""
it "escapes \\n" $
2020-09-30 05:14:52 +02:00
value minified (Full.String "\n") `shouldBe` "\"\\n\""
it "escapes \\r" $
2020-09-30 05:14:52 +02:00
value minified (Full.String "\r") `shouldBe` "\"\\r\""
it "escapes \\t" $
2020-09-30 05:14:52 +02:00
value minified (Full.String "\t") `shouldBe` "\"\\t\""
it "escapes backspace" $
2020-09-30 05:14:52 +02:00
value minified (Full.String "a\bc") `shouldBe` "\"a\\bc\""
context "escapes Unicode for chars less than 0010" $ do
2020-09-30 05:14:52 +02:00
it "Null" $ value minified (Full.String "\x0000") `shouldBe` "\"\\u0000\""
it "bell" $ value minified (Full.String "\x0007") `shouldBe` "\"\\u0007\""
context "escapes Unicode for char less than 0020" $ do
2020-09-30 05:14:52 +02:00
it "DLE" $ value minified (Full.String "\x0010") `shouldBe` "\"\\u0010\""
it "EM" $ value minified (Full.String "\x0019") `shouldBe` "\"\\u0019\""
context "encodes without escape" $ do
2020-09-30 05:14:52 +02:00
it "space" $ value minified (Full.String "\x0020") `shouldBe` "\" \""
it "~" $ value minified (Full.String "\x007E") `shouldBe` "\"~\""
context "pretty" $ do
it "uses strings for short string values" $
2020-09-30 05:14:52 +02:00
value pretty (Full.String "Short text") `shouldBe` "\"Short text\""
it "uses block strings for text with new lines, with newline symbol" $
2021-09-23 08:23:38 +02:00
let expected = [gql|
"""
Line 1
Line 2
"""
|]
actual = value pretty $ Full.String "Line 1\nLine 2"
in actual `shouldBe` expected
it "uses block strings for text with new lines, with CR symbol" $
2021-09-23 08:23:38 +02:00
let expected = [gql|
"""
Line 1
Line 2
"""
|]
actual = value pretty $ Full.String "Line 1\rLine 2"
in actual `shouldBe` expected
it "uses block strings for text with new lines, with CR symbol followed by newline" $
2021-09-23 08:23:38 +02:00
let expected = [gql|
"""
Line 1
Line 2
"""
|]
actual = value pretty $ Full.String "Line 1\r\nLine 2"
in actual `shouldBe` expected
it "encodes as one line string if has escaped symbols" $ do
let
genNotAllowedSymbol = oneof
[ choose ('\x0000', '\x0008')
, choose ('\x000B', '\x000C')
, choose ('\x000E', '\x001F')
, pure '\x007F'
]
forAll genNotAllowedSymbol $ \x -> do
let
2021-09-23 08:23:38 +02:00
rawValue = "Short \n" <> Text.Lazy.cons x "text"
encoded = value pretty
$ Full.String $ Text.Lazy.toStrict rawValue
shouldStartWith (Text.Lazy.unpack encoded) "\""
shouldEndWith (Text.Lazy.unpack encoded) "\""
shouldNotContain (Text.Lazy.unpack encoded) "\"\"\""
it "Hello world" $
let actual = value pretty
$ Full.String "Hello,\n World!\n\nYours,\n GraphQL."
expected = [gql|
"""
Hello,
World!
Yours,
GraphQL.
"""
|]
in actual `shouldBe` expected
it "has only newlines" $
let actual = value pretty $ Full.String "\n"
expected = [gql|
"""
"""
|]
in actual `shouldBe` expected
it "has newlines and one symbol at the begining" $
2021-09-23 08:23:38 +02:00
let actual = value pretty $ Full.String "a\n\n"
expected = [gql|
"""
a
2021-09-23 08:23:38 +02:00
"""|]
in actual `shouldBe` expected
it "has newlines and one symbol at the end" $
2021-09-23 08:23:38 +02:00
let actual = value pretty $ Full.String "\n\na"
expected = [gql|
"""
2021-09-23 08:23:38 +02:00
a
"""
|]
in actual `shouldBe` expected
it "has newlines and one symbol in the middle" $
2021-09-23 08:23:38 +02:00
let actual = value pretty $ Full.String "\na\n"
expected = [gql|
"""
a
"""
|]
in actual `shouldBe` expected
it "skip trailing whitespaces" $
let actual = value pretty $ Full.String " Short\ntext "
expected = [gql|
"""
Short
text
"""
|]
in actual `shouldBe` expected
describe "definition" $
it "indents block strings in arguments" $
2020-09-30 05:14:52 +02:00
let location = Full.Location 0 0
argumentValue = Full.Node (Full.String "line1\nline2") location
arguments = [Full.Argument "message" argumentValue location]
field = Full.Field Nothing "field" arguments [] [] location
fieldSelection = pure $ Full.FieldSelection field
operation = Full.DefinitionOperation
$ Full.SelectionSet fieldSelection location
2021-09-23 08:23:38 +02:00
expected = Text.Lazy.snoc [gql|
{
field(message: """
line1
line2
""")
}
|] '\n'
actual = definition pretty operation
in actual `shouldBe` expected
2022-10-02 11:38:53 +02:00
describe "operationType" $
it "produces lowercase mutation operation type" $
let actual = operationType pretty Full.Mutation
in actual `shouldBe` "mutation"
2022-12-25 16:38:00 +01:00
describe "typeSystemDefinition" $ do
2022-12-25 16:38:00 +01:00
it "produces a schema with an indented operation type definition" $
let queryType = Full.OperationTypeDefinition Full.Query "QueryRootType"
mutationType = Full.OperationTypeDefinition Full.Mutation "MutationType"
operations = queryType :| pure mutationType
definition' = Full.SchemaDefinition [] operations
expected = Text.Lazy.snoc [gql|
schema {
query: QueryRootType
mutation: MutationType
}
|] '\n'
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected
it "encodes a scalar type definition" $
let uuidType = Full.ScalarTypeDefinition mempty "UUID" mempty
definition' = Full.TypeDefinition uuidType
expected = "scalar UUID"
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected
2023-01-02 10:30:37 +01:00
it "encodes an interface definition" $
let someType = Full.TypeNamed "String"
argument = Full.InputValueDefinition mempty "arg" someType Nothing mempty
arguments = Full.ArgumentsDefinition [argument]
definition' = Full.TypeDefinition
$ Full.InterfaceTypeDefinition mempty "UUID" mempty
$ pure
$ Full.FieldDefinition mempty "value" arguments someType mempty
expected = [gql|
interface UUID {
value(arg: String): String
}
|]
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected
2023-01-08 17:33:25 +01:00
2023-01-09 20:56:21 +01:00
it "encodes an union definition" $
2023-01-08 17:33:25 +01:00
let definition' = Full.TypeDefinition
$ Full.UnionTypeDefinition mempty "SearchResult" mempty
$ Full.UnionMemberTypes ["Photo", "Person"]
expected = [gql|
union SearchResult =
| Photo
| Person
|]
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected
2023-01-09 20:56:21 +01:00
it "encodes an enum definition" $
let values =
[ Full.EnumValueDefinition mempty "NORTH" mempty
, Full.EnumValueDefinition mempty "EAST" mempty
, Full.EnumValueDefinition mempty "SOUTH" mempty
, Full.EnumValueDefinition mempty "WEST" mempty
]
definition' = Full.TypeDefinition
$ Full.EnumTypeDefinition mempty "Direction" mempty values
expected = [gql|
enum Direction {
NORTH
EAST
SOUTH
WEST
}
|]
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected
2023-01-10 09:53:18 +01:00
it "encodes an input type" $
let intType = Full.TypeNonNull $ Full.NonNullTypeNamed "Int"
stringType = Full.TypeNamed "String"
fields =
[ Full.InputValueDefinition mempty "a" stringType Nothing mempty
, Full.InputValueDefinition mempty "b" intType Nothing mempty
]
definition' = Full.TypeDefinition
$ Full.InputObjectTypeDefinition mempty "ExampleInputObject" mempty fields
expected = [gql|
input ExampleInputObject {
a: String
b: Int!
}
|]
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected