Replace gql in Encoder tests with multiline string
All checks were successful
Build / audit (push) Successful in 17s
Build / test (push) Successful in 6m16s
Build / doc (push) Successful in 5m16s

This commit is contained in:
Eugen Wissner 2024-10-14 20:50:34 +02:00
parent ba07f8298b
commit b056b4256f
Signed by: belka
GPG Key ID: A27FDC1E8EE902C0
3 changed files with 117 additions and 160 deletions

View File

@ -1,5 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Language.GraphQL.AST.EncoderSpec
( spec
) where
@ -7,7 +6,6 @@ module Language.GraphQL.AST.EncoderSpec
import Data.List.NonEmpty (NonEmpty(..))
import qualified Language.GraphQL.AST.Document as Full
import Language.GraphQL.AST.Encoder
import Language.GraphQL.TH
import Test.Hspec (Spec, context, describe, it, shouldBe, shouldStartWith, shouldEndWith, shouldNotContain)
import Test.QuickCheck (choose, oneof, forAll)
import qualified Data.Text.Lazy as Text.Lazy
@ -50,110 +48,89 @@ spec = do
it "uses strings for short string values" $
value pretty (Full.String "Short text") `shouldBe` "\"Short text\""
it "uses block strings for text with new lines, with newline symbol" $
let expected = [gql|
"""
Line 1
Line 2
"""
|]
let expected = "\"\"\"\n\
\ Line 1\n\
\ Line 2\n\
\\"\"\""
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" $
let expected = [gql|
"""
Line 1
Line 2
"""
|]
let expected = "\"\"\"\n\
\ Line 1\n\
\ Line 2\n\
\\"\"\""
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" $
let expected = [gql|
"""
Line 1
Line 2
"""
|]
let expected = "\"\"\"\n\
\ Line 1\n\
\ Line 2\n\
\\"\"\""
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'
]
let genNotAllowedSymbol = oneof
[ choose ('\x0000', '\x0008')
, choose ('\x000B', '\x000C')
, choose ('\x000E', '\x001F')
, pure '\x007F'
]
forAll genNotAllowedSymbol $ \x -> do
let
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) "\"\"\""
let rawValue = "Short \n" <> Text.Lazy.cons x "text"
encoded = Text.Lazy.unpack
$ value pretty
$ Full.String
$ Text.Lazy.toStrict rawValue
shouldStartWith encoded "\""
shouldEndWith encoded "\""
shouldNotContain encoded "\"\"\""
it "Hello world" $
let actual = value pretty
$ Full.String "Hello,\n World!\n\nYours,\n GraphQL."
expected = [gql|
"""
Hello,
World!
Yours,
GraphQL.
"""
|]
expected = "\"\"\"\n\
\ Hello,\n\
\ World!\n\
\\n\
\ Yours,\n\
\ GraphQL.\n\
\\"\"\""
in actual `shouldBe` expected
it "has only newlines" $
let actual = value pretty $ Full.String "\n"
expected = [gql|
"""
"""
|]
expected = "\"\"\"\n\n\n\"\"\""
in actual `shouldBe` expected
it "has newlines and one symbol at the begining" $
let actual = value pretty $ Full.String "a\n\n"
expected = [gql|
"""
a
"""|]
expected = "\"\"\"\n\
\ a\n\
\\n\
\\n\
\\"\"\""
in actual `shouldBe` expected
it "has newlines and one symbol at the end" $
let actual = value pretty $ Full.String "\n\na"
expected = [gql|
"""
a
"""
|]
expected = "\"\"\"\n\
\\n\
\\n\
\ a\n\
\\"\"\""
in actual `shouldBe` expected
it "has newlines and one symbol in the middle" $
let actual = value pretty $ Full.String "\na\n"
expected = [gql|
"""
a
"""
|]
expected = "\"\"\"\n\
\\n\
\ a\n\
\\n\
\\"\"\""
in actual `shouldBe` expected
it "skip trailing whitespaces" $
let actual = value pretty $ Full.String " Short\ntext "
expected = [gql|
"""
Short
text
"""
|]
expected = "\"\"\"\n\
\ Short\n\
\ text\n\
\\"\"\""
in actual `shouldBe` expected
describe "definition" $
@ -165,14 +142,12 @@ spec = do
fieldSelection = pure $ Full.FieldSelection field
operation = Full.DefinitionOperation
$ Full.SelectionSet fieldSelection location
expected = Text.Lazy.snoc [gql|
{
field(message: """
line1
line2
""")
}
|] '\n'
expected = "{\n\
\ field(message: \"\"\"\n\
\ line1\n\
\ line2\n\
\ \"\"\")\n\
\}\n"
actual = definition pretty operation
in actual `shouldBe` expected
@ -187,12 +162,10 @@ spec = do
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'
expected = "schema {\n\
\ query: QueryRootType\n\
\ mutation: MutationType\n\
\}\n"
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected
@ -211,11 +184,9 @@ spec = do
$ Full.InterfaceTypeDefinition mempty "UUID" mempty
$ pure
$ Full.FieldDefinition mempty "value" arguments someType mempty
expected = [gql|
interface UUID {
value(arg: String): String
}
|]
expected = "interface UUID {\n\
\ value(arg: String): String\n\
\}"
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected
@ -223,11 +194,9 @@ spec = do
let definition' = Full.TypeDefinition
$ Full.UnionTypeDefinition mempty "SearchResult" mempty
$ Full.UnionMemberTypes ["Photo", "Person"]
expected = [gql|
union SearchResult =
| Photo
| Person
|]
expected = "union SearchResult =\n\
\ | Photo\n\
\ | Person"
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected
@ -240,14 +209,12 @@ spec = do
]
definition' = Full.TypeDefinition
$ Full.EnumTypeDefinition mempty "Direction" mempty values
expected = [gql|
enum Direction {
NORTH
EAST
SOUTH
WEST
}
|]
expected = "enum Direction {\n\
\ NORTH\n\
\ EAST\n\
\ SOUTH\n\
\ WEST\n\
\}"
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected
@ -260,12 +227,10 @@ spec = do
]
definition' = Full.TypeDefinition
$ Full.InputObjectTypeDefinition mempty "ExampleInputObject" mempty fields
expected = [gql|
input ExampleInputObject {
a: String
b: Int!
}
|]
expected = "input ExampleInputObject {\n\
\ a: String\n\
\ b: Int!\n\
\}"
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected
@ -274,10 +239,8 @@ spec = do
let definition' = Full.DirectiveDefinition mempty "example" mempty False
$ pure
$ DirectiveLocation.ExecutableDirectiveLocation DirectiveLocation.Field
expected = [gql|
@example() on
| FIELD
|]
expected = "@example() on\n\
\ | FIELD"
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected
@ -285,9 +248,7 @@ spec = do
let definition' = Full.DirectiveDefinition mempty "example" mempty True
$ pure
$ DirectiveLocation.ExecutableDirectiveLocation DirectiveLocation.Field
expected = [gql|
@example() repeatable on
| FIELD
|]
expected = "@example() repeatable on\n\
\ | FIELD"
actual = typeSystemDefinition pretty definition'
in actual `shouldBe` expected

View File

@ -1,5 +1,4 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Language.GraphQL.AST.LexerSpec
( spec
) where
@ -7,7 +6,6 @@ module Language.GraphQL.AST.LexerSpec
import Data.Text (Text)
import Data.Void (Void)
import Language.GraphQL.AST.Lexer
import Language.GraphQL.TH
import Test.Hspec (Spec, context, describe, it)
import Test.Hspec.Megaparsec (shouldParse, shouldFailOn, shouldSucceedOn)
import Text.Megaparsec (ParseErrorBundle, parse)
@ -19,38 +17,39 @@ spec = describe "Lexer" $ do
parse unicodeBOM "" `shouldSucceedOn` "\xfeff"
it "lexes strings" $ do
parse string "" [gql|"simple"|] `shouldParse` "simple"
parse string "" [gql|" white space "|] `shouldParse` " white space "
parse string "" [gql|"quote \""|] `shouldParse` [gql|quote "|]
parse string "" [gql|"escaped \n"|] `shouldParse` "escaped \n"
parse string "" [gql|"slashes \\ \/"|] `shouldParse` [gql|slashes \ /|]
parse string "" [gql|"unicode \u1234\u5678\u90AB\uCDEF"|]
parse string "" "\"simple\"" `shouldParse` "simple"
parse string "" "\" white space \"" `shouldParse` " white space "
parse string "" "\"quote \\\"\"" `shouldParse` "quote \""
parse string "" "\"escaped \\n\"" `shouldParse` "escaped \n"
parse string "" "\"slashes \\\\ \\/\"" `shouldParse` "slashes \\ /"
parse string "" "\"unicode \\u1234\\u5678\\u90AB\\uCDEF\""
`shouldParse` "unicode ሴ噸邫췯"
it "lexes block string" $ do
parse blockString "" [gql|"""simple"""|] `shouldParse` "simple"
parse blockString "" [gql|""" white space """|]
parse blockString "" "\"\"\"simple\"\"\"" `shouldParse` "simple"
parse blockString "" "\"\"\" white space \"\"\""
`shouldParse` " white space "
parse blockString "" [gql|"""contains " quote"""|]
`shouldParse` [gql|contains " quote|]
parse blockString "" [gql|"""contains \""" triplequote"""|]
`shouldParse` [gql|contains """ triplequote|]
parse blockString "" "\"\"\"contains \" quote\"\"\""
`shouldParse` "contains \" quote"
parse blockString "" "\"\"\"contains \\\"\"\" triplequote\"\"\""
`shouldParse` "contains \"\"\" triplequote"
parse blockString "" "\"\"\"multi\nline\"\"\"" `shouldParse` "multi\nline"
parse blockString "" "\"\"\"multi\rline\r\nnormalized\"\"\""
`shouldParse` "multi\nline\nnormalized"
parse blockString "" "\"\"\"multi\rline\r\nnormalized\"\"\""
`shouldParse` "multi\nline\nnormalized"
parse blockString "" [gql|"""unescaped \n\r\b\t\f\u1234"""|]
`shouldParse` [gql|unescaped \n\r\b\t\f\u1234|]
parse blockString "" [gql|"""slashes \\ \/"""|]
`shouldParse` [gql|slashes \\ \/|]
parse blockString "" [gql|"""
spans
multiple
lines
"""|] `shouldParse` "spans\n multiple\n lines"
parse blockString "" "\"\"\"unescaped \\n\\r\\b\\t\\f\\u1234\"\"\""
`shouldParse` "unescaped \\n\\r\\b\\t\\f\\u1234"
parse blockString "" "\"\"\"slashes \\\\ \\/\"\"\""
`shouldParse` "slashes \\\\ \\/"
parse blockString "" "\"\"\"\n\
\\n\
\ spans\n\
\ multiple\n\
\ lines\n\
\\n\
\\"\"\""
`shouldParse` "spans\n multiple\n lines"
it "lexes numbers" $ do
parse integer "" "4" `shouldParse` (4 :: Int)
@ -84,7 +83,7 @@ spec = describe "Lexer" $ do
context "Implementation tests" $ do
it "lexes empty block strings" $
parse blockString "" [gql|""""""|] `shouldParse` ""
parse blockString "" "\"\"\"\"\"\"" `shouldParse` ""
it "lexes ampersand" $
parse amp "" "&" `shouldParse` "&"
it "lexes schema extensions" $

View File

@ -5,9 +5,7 @@
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE QuasiQuotes #-}
module Language.GraphQL.ExecuteSpec
( spec
@ -23,7 +21,6 @@ import Language.GraphQL.AST (Document, Location(..), Name)
import Language.GraphQL.AST.Parser (document)
import Language.GraphQL.Error
import Language.GraphQL.Execute (execute)
import Language.GraphQL.TH
import qualified Language.GraphQL.Type.Schema as Schema
import qualified Language.GraphQL.Type as Type
import Language.GraphQL.Type
@ -269,15 +266,15 @@ spec :: Spec
spec =
describe "execute" $ do
it "rejects recursive fragments" $
let sourceQuery = [gql|
{
...cyclicFragment
}
fragment cyclicFragment on Query {
...cyclicFragment
}
|]
let sourceQuery = "\
\{\n\
\ ...cyclicFragment\n\
\}\n\
\\n\
\fragment cyclicFragment on Query {\n\
\ ...cyclicFragment\n\
\}\
\"
expected = Response (Object mempty) mempty
in sourceQuery `shouldResolveTo` expected