parent
1e55f17e7e
commit
b215e1a4a7
@ -13,6 +13,7 @@ All notable changes to this project will be documented in this file.
|
|||||||
|
|
||||||
### Added
|
### Added
|
||||||
- Directive support (@skip and @include).
|
- Directive support (@skip and @include).
|
||||||
|
- Pretifying multi-line string arguments as block strings.
|
||||||
|
|
||||||
## [0.6.0.0] - 2019-11-27
|
## [0.6.0.0] - 2019-11-27
|
||||||
### Changed
|
### Changed
|
||||||
|
@ -37,8 +37,8 @@ dependencies:
|
|||||||
library:
|
library:
|
||||||
source-dirs: src
|
source-dirs: src
|
||||||
other-modules:
|
other-modules:
|
||||||
- Language.GraphQL.Execute.Transform
|
- Language.GraphQL.Execute.Transform
|
||||||
- Language.GraphQL.Type.Directive
|
- Language.GraphQL.Type.Directive
|
||||||
|
|
||||||
tests:
|
tests:
|
||||||
tasty:
|
tasty:
|
||||||
|
@ -21,6 +21,7 @@ import Data.Text (Text)
|
|||||||
import qualified Data.Text as Text
|
import qualified Data.Text as Text
|
||||||
import qualified Data.Text.Lazy as Lazy (Text)
|
import qualified Data.Text.Lazy as Lazy (Text)
|
||||||
import qualified Data.Text.Lazy as Lazy.Text
|
import qualified Data.Text.Lazy as Lazy.Text
|
||||||
|
import Data.Text.Lazy.Builder (Builder)
|
||||||
import qualified Data.Text.Lazy.Builder as Builder
|
import qualified Data.Text.Lazy.Builder as Builder
|
||||||
import Data.Text.Lazy.Builder.Int (decimal, hexadecimal)
|
import Data.Text.Lazy.Builder.Int (decimal, hexadecimal)
|
||||||
import Data.Text.Lazy.Builder.RealFloat (realFloat)
|
import Data.Text.Lazy.Builder.RealFloat (realFloat)
|
||||||
@ -109,40 +110,47 @@ selectionSet formatter
|
|||||||
selectionSetOpt :: Formatter -> Full.SelectionSetOpt -> Lazy.Text
|
selectionSetOpt :: Formatter -> Full.SelectionSetOpt -> Lazy.Text
|
||||||
selectionSetOpt formatter = bracesList formatter $ selection formatter
|
selectionSetOpt formatter = bracesList formatter $ selection formatter
|
||||||
|
|
||||||
|
indent :: (Integral a) => a -> Lazy.Text
|
||||||
|
indent indentation = Lazy.Text.replicate (fromIntegral indentation) " "
|
||||||
|
|
||||||
selection :: Formatter -> Full.Selection -> Lazy.Text
|
selection :: Formatter -> Full.Selection -> Lazy.Text
|
||||||
selection formatter = Lazy.Text.append indent . f
|
selection formatter = Lazy.Text.append indent' . encodeSelection
|
||||||
where
|
where
|
||||||
f (Full.SelectionField x) = field incrementIndent x
|
encodeSelection (Full.SelectionField field') = field incrementIndent field'
|
||||||
f (Full.SelectionInlineFragment x) = inlineFragment incrementIndent x
|
encodeSelection (Full.SelectionInlineFragment fragment) =
|
||||||
f (Full.SelectionFragmentSpread x) = fragmentSpread incrementIndent x
|
inlineFragment incrementIndent fragment
|
||||||
|
encodeSelection (Full.SelectionFragmentSpread spread) =
|
||||||
|
fragmentSpread incrementIndent spread
|
||||||
incrementIndent
|
incrementIndent
|
||||||
| Pretty n <- formatter = Pretty $ n + 1
|
| Pretty indentation <- formatter = Pretty $ indentation + 1
|
||||||
| otherwise = Minified
|
| otherwise = Minified
|
||||||
indent
|
indent'
|
||||||
| Pretty n <- formatter = Lazy.Text.replicate (fromIntegral $ n + 1) " "
|
| Pretty indentation <- formatter = indent $ indentation + 1
|
||||||
| otherwise = mempty
|
| otherwise = ""
|
||||||
|
|
||||||
|
colon :: Formatter -> Lazy.Text
|
||||||
|
colon formatter = eitherFormat formatter ": " ":"
|
||||||
|
|
||||||
field :: Formatter -> Full.Field -> Lazy.Text
|
field :: Formatter -> Full.Field -> Lazy.Text
|
||||||
field formatter (Full.Field alias name args dirs selso)
|
field formatter (Full.Field alias name args dirs set)
|
||||||
= optempty (`Lazy.Text.append` colon) (Lazy.Text.fromStrict $ fold alias)
|
= optempty prependAlias (fold alias)
|
||||||
<> Lazy.Text.fromStrict name
|
<> Lazy.Text.fromStrict name
|
||||||
<> optempty (arguments formatter) args
|
<> optempty (arguments formatter) args
|
||||||
<> optempty (directives formatter) dirs
|
<> optempty (directives formatter) dirs
|
||||||
<> selectionSetOpt'
|
<> optempty selectionSetOpt' set
|
||||||
where
|
where
|
||||||
colon = eitherFormat formatter ": " ":"
|
prependAlias aliasName = Lazy.Text.fromStrict aliasName <> colon formatter
|
||||||
selectionSetOpt'
|
selectionSetOpt' = (eitherFormat formatter " " "" <>)
|
||||||
| null selso = mempty
|
. selectionSetOpt formatter
|
||||||
| otherwise = eitherFormat formatter " " mempty <> selectionSetOpt formatter selso
|
|
||||||
|
|
||||||
arguments :: Formatter -> [Full.Argument] -> Lazy.Text
|
arguments :: Formatter -> [Full.Argument] -> Lazy.Text
|
||||||
arguments formatter = parensCommas formatter $ argument formatter
|
arguments formatter = parensCommas formatter $ argument formatter
|
||||||
|
|
||||||
argument :: Formatter -> Full.Argument -> Lazy.Text
|
argument :: Formatter -> Full.Argument -> Lazy.Text
|
||||||
argument formatter (Full.Argument name v)
|
argument formatter (Full.Argument name value')
|
||||||
= Lazy.Text.fromStrict name
|
= Lazy.Text.fromStrict name
|
||||||
<> eitherFormat formatter ": " ":"
|
<> colon formatter
|
||||||
<> value formatter v
|
<> value formatter value'
|
||||||
|
|
||||||
-- * Fragments
|
-- * Fragments
|
||||||
|
|
||||||
@ -174,8 +182,8 @@ directive formatter (Full.Directive name args)
|
|||||||
= "@" <> Lazy.Text.fromStrict name <> optempty (arguments formatter) args
|
= "@" <> Lazy.Text.fromStrict name <> optempty (arguments formatter) args
|
||||||
|
|
||||||
directives :: Formatter -> [Full.Directive] -> Lazy.Text
|
directives :: Formatter -> [Full.Directive] -> Lazy.Text
|
||||||
directives formatter@(Pretty _) = Lazy.Text.cons ' ' . spaces (directive formatter)
|
|
||||||
directives Minified = spaces (directive Minified)
|
directives Minified = spaces (directive Minified)
|
||||||
|
directives formatter = Lazy.Text.cons ' ' . spaces (directive formatter)
|
||||||
|
|
||||||
-- | Converts a 'Full.Value' into a string.
|
-- | Converts a 'Full.Value' into a string.
|
||||||
value :: Formatter -> Full.Value -> Lazy.Text
|
value :: Formatter -> Full.Value -> Lazy.Text
|
||||||
@ -184,7 +192,7 @@ value _ (Full.Int x) = Builder.toLazyText $ decimal x
|
|||||||
value _ (Full.Float x) = Builder.toLazyText $ realFloat x
|
value _ (Full.Float x) = Builder.toLazyText $ realFloat x
|
||||||
value _ (Full.Boolean x) = booleanValue x
|
value _ (Full.Boolean x) = booleanValue x
|
||||||
value _ Full.Null = mempty
|
value _ Full.Null = mempty
|
||||||
value _ (Full.String x) = stringValue x
|
value formatter (Full.String string) = stringValue formatter string
|
||||||
value _ (Full.Enum x) = Lazy.Text.fromStrict x
|
value _ (Full.Enum x) = Lazy.Text.fromStrict x
|
||||||
value formatter (Full.List x) = listValue formatter x
|
value formatter (Full.List x) = listValue formatter x
|
||||||
value formatter (Full.Object x) = objectValue formatter x
|
value formatter (Full.Object x) = objectValue formatter x
|
||||||
@ -193,23 +201,39 @@ booleanValue :: Bool -> Lazy.Text
|
|||||||
booleanValue True = "true"
|
booleanValue True = "true"
|
||||||
booleanValue False = "false"
|
booleanValue False = "false"
|
||||||
|
|
||||||
stringValue :: Text -> Lazy.Text
|
stringValue :: Formatter -> Text -> Lazy.Text
|
||||||
stringValue string = Builder.toLazyText
|
stringValue Minified string = Builder.toLazyText
|
||||||
$ quote
|
$ quote <> Text.foldr (mappend . escape') quote string
|
||||||
<> Text.foldr (mappend . replace) quote string
|
|
||||||
where
|
where
|
||||||
replace char
|
|
||||||
| char == '\\' = Builder.fromString "\\\\"
|
|
||||||
| char == '\"' = Builder.fromString "\\\""
|
|
||||||
| char == '\b' = Builder.fromString "\\b"
|
|
||||||
| char == '\f' = Builder.fromString "\\f"
|
|
||||||
| char == '\n' = Builder.fromString "\\n"
|
|
||||||
| char == '\r' = Builder.fromString "\\r"
|
|
||||||
| char < '\x0010' = unicode "\\u000" char
|
|
||||||
| char < '\x0020' = unicode "\\u00" char
|
|
||||||
| otherwise = Builder.singleton char
|
|
||||||
quote = Builder.singleton '\"'
|
quote = Builder.singleton '\"'
|
||||||
unicode prefix char = Builder.fromString prefix <> hexadecimal (ord char)
|
escape' '\n' = Builder.fromString "\\n"
|
||||||
|
escape' char = escape char
|
||||||
|
stringValue (Pretty indentation) string = byStringType $ Text.lines string
|
||||||
|
where
|
||||||
|
byStringType [] = "\"\""
|
||||||
|
byStringType [line] = Builder.toLazyText
|
||||||
|
$ quote <> Text.foldr (mappend . escape) quote line
|
||||||
|
byStringType lines' = "\"\"\"\n"
|
||||||
|
<> Lazy.Text.unlines (transformLine <$> lines')
|
||||||
|
<> indent indentation
|
||||||
|
<> "\"\"\""
|
||||||
|
transformLine = (indent (indentation + 1) <>)
|
||||||
|
. Lazy.Text.fromStrict
|
||||||
|
. Text.replace "\"\"\"" "\\\"\"\""
|
||||||
|
quote = Builder.singleton '\"'
|
||||||
|
|
||||||
|
escape :: Char -> Builder
|
||||||
|
escape char'
|
||||||
|
| char' == '\\' = Builder.fromString "\\\\"
|
||||||
|
| char' == '\"' = Builder.fromString "\\\""
|
||||||
|
| char' == '\b' = Builder.fromString "\\b"
|
||||||
|
| char' == '\f' = Builder.fromString "\\f"
|
||||||
|
| char' == '\r' = Builder.fromString "\\r"
|
||||||
|
| char' < '\x0010' = unicode "\\u000" char'
|
||||||
|
| char' < '\x0020' = unicode "\\u00" char'
|
||||||
|
| otherwise = Builder.singleton char'
|
||||||
|
where
|
||||||
|
unicode prefix = mappend (Builder.fromString prefix) . (hexadecimal . ord)
|
||||||
|
|
||||||
listValue :: Formatter -> [Full.Value] -> Lazy.Text
|
listValue :: Formatter -> [Full.Value] -> Lazy.Text
|
||||||
listValue formatter = bracketsCommas formatter $ value formatter
|
listValue formatter = bracketsCommas formatter $ value formatter
|
||||||
@ -222,14 +246,9 @@ objectValue formatter = intercalate $ objectField formatter
|
|||||||
. Lazy.Text.intercalate (eitherFormat formatter ", " ",")
|
. Lazy.Text.intercalate (eitherFormat formatter ", " ",")
|
||||||
. fmap f
|
. fmap f
|
||||||
|
|
||||||
|
|
||||||
objectField :: Formatter -> Full.ObjectField -> Lazy.Text
|
objectField :: Formatter -> Full.ObjectField -> Lazy.Text
|
||||||
objectField formatter (Full.ObjectField name v)
|
objectField formatter (Full.ObjectField name value') =
|
||||||
= Lazy.Text.fromStrict name <> colon <> value formatter v
|
Lazy.Text.fromStrict name <> colon formatter <> value formatter value'
|
||||||
where
|
|
||||||
colon
|
|
||||||
| Pretty _ <- formatter = ": "
|
|
||||||
| Minified <- formatter = ":"
|
|
||||||
|
|
||||||
-- | Converts a 'Full.Type' a type into a string.
|
-- | Converts a 'Full.Type' a type into a string.
|
||||||
type' :: Full.Type -> Lazy.Text
|
type' :: Full.Type -> Lazy.Text
|
||||||
|
@ -1,23 +1,46 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
|
{-# LANGUAGE QuasiQuotes #-}
|
||||||
module Language.GraphQL.AST.EncoderSpec
|
module Language.GraphQL.AST.EncoderSpec
|
||||||
( spec
|
( spec
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Language.GraphQL.AST (Value(..))
|
import Language.GraphQL.AST
|
||||||
import Language.GraphQL.AST.Encoder
|
import Language.GraphQL.AST.Encoder
|
||||||
import Test.Hspec ( Spec
|
import Test.Hspec (Spec, context, describe, it, shouldBe)
|
||||||
, describe
|
import Text.RawString.QQ (r)
|
||||||
, it
|
|
||||||
, shouldBe
|
|
||||||
)
|
|
||||||
|
|
||||||
spec :: Spec
|
spec :: Spec
|
||||||
spec = describe "value" $ do
|
spec = do
|
||||||
it "escapes \\" $
|
describe "value" $ do
|
||||||
value minified (String "\\") `shouldBe` "\"\\\\\""
|
context "minified" $ do
|
||||||
it "escapes quotes" $
|
it "escapes \\" $
|
||||||
value minified (String "\"") `shouldBe` "\"\\\"\""
|
value minified (String "\\") `shouldBe` "\"\\\\\""
|
||||||
it "escapes backspace" $
|
it "escapes quotes" $
|
||||||
value minified (String "a\bc") `shouldBe` "\"a\\bc\""
|
value minified (String "\"") `shouldBe` "\"\\\"\""
|
||||||
it "escapes Unicode" $
|
it "escapes backspace" $
|
||||||
value minified (String "\0") `shouldBe` "\"\\u0000\""
|
value minified (String "a\bc") `shouldBe` "\"a\\bc\""
|
||||||
|
it "escapes Unicode" $
|
||||||
|
value minified (String "\0") `shouldBe` "\"\\u0000\""
|
||||||
|
|
||||||
|
context "pretty" $ do
|
||||||
|
it "uses strings for short string values" $
|
||||||
|
value pretty (String "Short text") `shouldBe` "\"Short text\""
|
||||||
|
it "uses block strings for text with new lines" $
|
||||||
|
value pretty (String "Line 1\nLine 2")
|
||||||
|
`shouldBe` "\"\"\"\n Line 1\n Line 2\n\"\"\""
|
||||||
|
it "escapes \\ in short strings" $
|
||||||
|
value pretty (String "\\") `shouldBe` "\"\\\\\""
|
||||||
|
|
||||||
|
describe "definition" $
|
||||||
|
it "indents block strings in arguments" $
|
||||||
|
let arguments = [Argument "message" (String "line1\nline2")]
|
||||||
|
field = Field Nothing "field" arguments [] []
|
||||||
|
set = OperationSelectionSet $ pure $ SelectionField field
|
||||||
|
operation = DefinitionOperation set
|
||||||
|
in definition pretty operation `shouldBe` [r|{
|
||||||
|
field(message: """
|
||||||
|
line1
|
||||||
|
line2
|
||||||
|
""")
|
||||||
|
}
|
||||||
|
|]
|
||||||
|
Loading…
Reference in New Issue
Block a user