Replace gql in Encoder tests with multiline string
This commit is contained in:
@@ -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
|
||||
|
Reference in New Issue
Block a user