Make all encoder functions return lazy text
This commit is contained in:
parent
f9dd363457
commit
a3354e7f58
@ -11,6 +11,7 @@ All notable changes to this project will be documented in this file.
|
|||||||
documents with multiple operations.
|
documents with multiple operations.
|
||||||
- `Language.GraphQL.Encoder.document` and other encoding functions take a
|
- `Language.GraphQL.Encoder.document` and other encoding functions take a
|
||||||
`Formatter` as argument to distinguish between minified and pretty printing.
|
`Formatter` as argument to distinguish between minified and pretty printing.
|
||||||
|
- All encoder functions return `Data.Text.Lazy`.
|
||||||
|
|
||||||
### Removed
|
### Removed
|
||||||
- Unused `Language.GraphQL.Encoder.spaced`.
|
- Unused `Language.GraphQL.Encoder.spaced`.
|
||||||
|
@ -1,7 +1,7 @@
|
|||||||
{-# LANGUAGE OverloadedStrings #-}
|
{-# LANGUAGE OverloadedStrings #-}
|
||||||
{-# LANGUAGE ExplicitForAll #-}
|
{-# LANGUAGE ExplicitForAll #-}
|
||||||
|
|
||||||
-- | This module defines a printer for the @GraphQL@ language.
|
-- | This module defines a minifier and a printer for the @GraphQL@ language.
|
||||||
module Language.GraphQL.Encoder
|
module Language.GraphQL.Encoder
|
||||||
( Formatter
|
( Formatter
|
||||||
, definition
|
, definition
|
||||||
@ -13,8 +13,11 @@ module Language.GraphQL.Encoder
|
|||||||
import Data.Foldable (fold)
|
import Data.Foldable (fold)
|
||||||
import Data.Monoid ((<>))
|
import Data.Monoid ((<>))
|
||||||
import qualified Data.List.NonEmpty as NonEmpty (toList)
|
import qualified Data.List.NonEmpty as NonEmpty (toList)
|
||||||
import Data.Text (Text, pack)
|
import Data.Text.Lazy (Text)
|
||||||
import qualified Data.Text as Text
|
import qualified Data.Text.Lazy as Text.Lazy
|
||||||
|
import Data.Text.Lazy.Builder (toLazyText)
|
||||||
|
import Data.Text.Lazy.Builder.Int (decimal)
|
||||||
|
import Data.Text.Lazy.Builder.RealFloat (realFloat)
|
||||||
import Language.GraphQL.AST
|
import Language.GraphQL.AST
|
||||||
|
|
||||||
-- | Instructs the encoder whether a GraphQL should be minified or pretty
|
-- | Instructs the encoder whether a GraphQL should be minified or pretty
|
||||||
@ -36,15 +39,15 @@ minified = Minified
|
|||||||
-- | Converts a 'Document' into a string.
|
-- | Converts a 'Document' into a string.
|
||||||
document :: Formatter -> Document -> Text
|
document :: Formatter -> Document -> Text
|
||||||
document formatter defs
|
document formatter defs
|
||||||
| Pretty _ <- formatter = Text.intercalate "\n" encodeDocument
|
| Pretty _ <- formatter = Text.Lazy.intercalate "\n" encodeDocument
|
||||||
| Minified <-formatter = Text.snoc (mconcat encodeDocument) '\n'
|
| Minified <-formatter = Text.Lazy.snoc (mconcat encodeDocument) '\n'
|
||||||
where
|
where
|
||||||
encodeDocument = NonEmpty.toList $ definition formatter <$> defs
|
encodeDocument = NonEmpty.toList $ definition formatter <$> defs
|
||||||
|
|
||||||
-- | Converts a 'Definition' into a string.
|
-- | Converts a 'Definition' into a string.
|
||||||
definition :: Formatter -> Definition -> Text
|
definition :: Formatter -> Definition -> Text
|
||||||
definition formatter x
|
definition formatter x
|
||||||
| Pretty _ <- formatter = Text.snoc (encodeDefinition x) '\n'
|
| Pretty _ <- formatter = Text.Lazy.snoc (encodeDefinition x) '\n'
|
||||||
| Minified <- formatter = encodeDefinition x
|
| Minified <- formatter = encodeDefinition x
|
||||||
where
|
where
|
||||||
encodeDefinition (DefinitionOperation operation)
|
encodeDefinition (DefinitionOperation operation)
|
||||||
@ -67,7 +70,7 @@ node :: Formatter
|
|||||||
-> SelectionSet
|
-> SelectionSet
|
||||||
-> Text
|
-> Text
|
||||||
node formatter name vars dirs sels
|
node formatter name vars dirs sels
|
||||||
= fold name
|
= Text.Lazy.fromStrict (fold name)
|
||||||
<> optempty (variableDefinitions formatter) vars
|
<> optempty (variableDefinitions formatter) vars
|
||||||
<> optempty (directives formatter) dirs
|
<> optempty (directives formatter) dirs
|
||||||
<> eitherFormat formatter " " mempty
|
<> eitherFormat formatter " " mempty
|
||||||
@ -90,7 +93,7 @@ defaultValue formatter val
|
|||||||
<> value formatter val
|
<> value formatter val
|
||||||
|
|
||||||
variable :: Name -> Text
|
variable :: Name -> Text
|
||||||
variable var = "$" <> var
|
variable var = "$" <> Text.Lazy.fromStrict var
|
||||||
|
|
||||||
selectionSet :: Formatter -> SelectionSet -> Text
|
selectionSet :: Formatter -> SelectionSet -> Text
|
||||||
selectionSet formatter
|
selectionSet formatter
|
||||||
@ -101,7 +104,7 @@ selectionSetOpt :: Formatter -> SelectionSetOpt -> Text
|
|||||||
selectionSetOpt formatter = bracesList formatter $ selection formatter
|
selectionSetOpt formatter = bracesList formatter $ selection formatter
|
||||||
|
|
||||||
selection :: Formatter -> Selection -> Text
|
selection :: Formatter -> Selection -> Text
|
||||||
selection formatter = Text.append indent . f
|
selection formatter = Text.Lazy.append indent . f
|
||||||
where
|
where
|
||||||
f (SelectionField x) = field incrementIndent x
|
f (SelectionField x) = field incrementIndent x
|
||||||
f (SelectionInlineFragment x) = inlineFragment incrementIndent x
|
f (SelectionInlineFragment x) = inlineFragment incrementIndent x
|
||||||
@ -110,13 +113,13 @@ selection formatter = Text.append indent . f
|
|||||||
| Pretty n <- formatter = Pretty $ n + 1
|
| Pretty n <- formatter = Pretty $ n + 1
|
||||||
| otherwise = Minified
|
| otherwise = Minified
|
||||||
indent
|
indent
|
||||||
| Pretty n <- formatter = Text.replicate (fromIntegral $ n + 1) " "
|
| Pretty n <- formatter = Text.Lazy.replicate (fromIntegral $ n + 1) " "
|
||||||
| otherwise = mempty
|
| otherwise = mempty
|
||||||
|
|
||||||
field :: Formatter -> Field -> Text
|
field :: Formatter -> Field -> Text
|
||||||
field formatter (Field alias name args dirs selso)
|
field formatter (Field alias name args dirs selso)
|
||||||
= optempty (`Text.append` colon) (fold alias)
|
= optempty (`Text.Lazy.append` colon) (Text.Lazy.fromStrict $ fold alias)
|
||||||
<> name
|
<> Text.Lazy.fromStrict name
|
||||||
<> optempty (arguments formatter) args
|
<> optempty (arguments formatter) args
|
||||||
<> optempty (directives formatter) dirs
|
<> optempty (directives formatter) dirs
|
||||||
<> selectionSetOpt'
|
<> selectionSetOpt'
|
||||||
@ -131,7 +134,7 @@ arguments formatter = parensCommas formatter $ argument formatter
|
|||||||
|
|
||||||
argument :: Formatter -> Argument -> Text
|
argument :: Formatter -> Argument -> Text
|
||||||
argument formatter (Argument name v)
|
argument formatter (Argument name v)
|
||||||
= name
|
= Text.Lazy.fromStrict name
|
||||||
<> eitherFormat formatter ": " ":"
|
<> eitherFormat formatter ": " ":"
|
||||||
<> value formatter v
|
<> value formatter v
|
||||||
|
|
||||||
@ -139,18 +142,20 @@ argument formatter (Argument name v)
|
|||||||
|
|
||||||
fragmentSpread :: Formatter -> FragmentSpread -> Text
|
fragmentSpread :: Formatter -> FragmentSpread -> Text
|
||||||
fragmentSpread formatter (FragmentSpread name ds)
|
fragmentSpread formatter (FragmentSpread name ds)
|
||||||
= "..." <> name <> optempty (directives formatter) ds
|
= "..." <> Text.Lazy.fromStrict name <> optempty (directives formatter) ds
|
||||||
|
|
||||||
inlineFragment :: Formatter -> InlineFragment -> Text
|
inlineFragment :: Formatter -> InlineFragment -> Text
|
||||||
inlineFragment formatter (InlineFragment tc dirs sels)
|
inlineFragment formatter (InlineFragment tc dirs sels)
|
||||||
= "... on " <> fold tc
|
= "... on "
|
||||||
|
<> Text.Lazy.fromStrict (fold tc)
|
||||||
<> directives formatter dirs
|
<> directives formatter dirs
|
||||||
<> eitherFormat formatter " " mempty
|
<> eitherFormat formatter " " mempty
|
||||||
<> selectionSet formatter sels
|
<> selectionSet formatter sels
|
||||||
|
|
||||||
fragmentDefinition :: Formatter -> FragmentDefinition -> Text
|
fragmentDefinition :: Formatter -> FragmentDefinition -> Text
|
||||||
fragmentDefinition formatter (FragmentDefinition name tc dirs sels)
|
fragmentDefinition formatter (FragmentDefinition name tc dirs sels)
|
||||||
= "fragment " <> name <> " on " <> tc
|
= "fragment " <> Text.Lazy.fromStrict name
|
||||||
|
<> " on " <> Text.Lazy.fromStrict tc
|
||||||
<> optempty (directives formatter) dirs
|
<> optempty (directives formatter) dirs
|
||||||
<> eitherFormat formatter " " mempty
|
<> eitherFormat formatter " " mempty
|
||||||
<> selectionSet formatter sels
|
<> selectionSet formatter sels
|
||||||
@ -159,14 +164,12 @@ fragmentDefinition formatter (FragmentDefinition name tc dirs sels)
|
|||||||
|
|
||||||
value :: Formatter -> Value -> Text
|
value :: Formatter -> Value -> Text
|
||||||
value _ (ValueVariable x) = variable x
|
value _ (ValueVariable x) = variable x
|
||||||
-- TODO: This will be replaced with `decimal` Builder
|
value _ (ValueInt x) = toLazyText $ decimal x
|
||||||
value _ (ValueInt x) = pack $ show x
|
value _ (ValueFloat x) = toLazyText $ realFloat x
|
||||||
-- TODO: This will be replaced with `decimal` Builder
|
|
||||||
value _ (ValueFloat x) = pack $ show x
|
|
||||||
value _ (ValueBoolean x) = booleanValue x
|
value _ (ValueBoolean x) = booleanValue x
|
||||||
value _ ValueNull = mempty
|
value _ ValueNull = mempty
|
||||||
value _ (ValueString x) = stringValue x
|
value _ (ValueString x) = stringValue $ Text.Lazy.fromStrict x
|
||||||
value _ (ValueEnum x) = x
|
value _ (ValueEnum x) = Text.Lazy.fromStrict x
|
||||||
value formatter (ValueList x) = listValue formatter x
|
value formatter (ValueList x) = listValue formatter x
|
||||||
value formatter (ValueObject x) = objectValue formatter x
|
value formatter (ValueObject x) = objectValue formatter x
|
||||||
|
|
||||||
@ -186,12 +189,13 @@ objectValue formatter = intercalate $ objectField formatter
|
|||||||
where
|
where
|
||||||
intercalate f
|
intercalate f
|
||||||
= braces
|
= braces
|
||||||
. Text.intercalate (eitherFormat formatter ", " ",")
|
. Text.Lazy.intercalate (eitherFormat formatter ", " ",")
|
||||||
. fmap f
|
. fmap f
|
||||||
|
|
||||||
|
|
||||||
objectField :: Formatter -> ObjectField -> Text
|
objectField :: Formatter -> ObjectField -> Text
|
||||||
objectField formatter (ObjectField name v) = name <> colon <> value formatter v
|
objectField formatter (ObjectField name v)
|
||||||
|
= Text.Lazy.fromStrict name <> colon <> value formatter v
|
||||||
where
|
where
|
||||||
colon
|
colon
|
||||||
| Pretty _ <- formatter = ": "
|
| Pretty _ <- formatter = ": "
|
||||||
@ -200,17 +204,17 @@ objectField formatter (ObjectField name v) = name <> colon <> value formatter v
|
|||||||
-- * Directives
|
-- * Directives
|
||||||
|
|
||||||
directives :: Formatter -> [Directive] -> Text
|
directives :: Formatter -> [Directive] -> Text
|
||||||
directives formatter@(Pretty _) = Text.cons ' ' . spaces (directive formatter)
|
directives formatter@(Pretty _) = Text.Lazy.cons ' ' . spaces (directive formatter)
|
||||||
directives Minified = spaces (directive Minified)
|
directives Minified = spaces (directive Minified)
|
||||||
|
|
||||||
directive :: Formatter -> Directive -> Text
|
directive :: Formatter -> Directive -> Text
|
||||||
directive formatter (Directive name args)
|
directive formatter (Directive name args)
|
||||||
= "@" <> name <> optempty (arguments formatter) args
|
= "@" <> Text.Lazy.fromStrict name <> optempty (arguments formatter) args
|
||||||
|
|
||||||
-- * Type Reference
|
-- * Type Reference
|
||||||
|
|
||||||
type_ :: Type -> Text
|
type_ :: Type -> Text
|
||||||
type_ (TypeNamed x) = x
|
type_ (TypeNamed x) = Text.Lazy.fromStrict x
|
||||||
type_ (TypeList x) = listType x
|
type_ (TypeList x) = listType x
|
||||||
type_ (TypeNonNull x) = nonNullType x
|
type_ (TypeNonNull x) = nonNullType x
|
||||||
|
|
||||||
@ -218,13 +222,13 @@ listType :: Type -> Text
|
|||||||
listType x = brackets (type_ x)
|
listType x = brackets (type_ x)
|
||||||
|
|
||||||
nonNullType :: NonNullType -> Text
|
nonNullType :: NonNullType -> Text
|
||||||
nonNullType (NonNullTypeNamed x) = x <> "!"
|
nonNullType (NonNullTypeNamed x) = Text.Lazy.fromStrict x <> "!"
|
||||||
nonNullType (NonNullTypeList x) = listType x <> "!"
|
nonNullType (NonNullTypeList x) = listType x <> "!"
|
||||||
|
|
||||||
-- * Internal
|
-- * Internal
|
||||||
|
|
||||||
between :: Char -> Char -> Text -> Text
|
between :: Char -> Char -> Text -> Text
|
||||||
between open close = Text.cons open . (`Text.snoc` close)
|
between open close = Text.Lazy.cons open . (`Text.Lazy.snoc` close)
|
||||||
|
|
||||||
parens :: Text -> Text
|
parens :: Text -> Text
|
||||||
parens = between '(' ')'
|
parens = between '(' ')'
|
||||||
@ -239,27 +243,27 @@ quotes :: Text -> Text
|
|||||||
quotes = between '"' '"'
|
quotes = between '"' '"'
|
||||||
|
|
||||||
spaces :: forall a. (a -> Text) -> [a] -> Text
|
spaces :: forall a. (a -> Text) -> [a] -> Text
|
||||||
spaces f = Text.intercalate "\SP" . fmap f
|
spaces f = Text.Lazy.intercalate "\SP" . fmap f
|
||||||
|
|
||||||
parensCommas :: forall a. Formatter -> (a -> Text) -> [a] -> Text
|
parensCommas :: forall a. Formatter -> (a -> Text) -> [a] -> Text
|
||||||
parensCommas formatter f
|
parensCommas formatter f
|
||||||
= parens
|
= parens
|
||||||
. Text.intercalate (eitherFormat formatter ", " ",")
|
. Text.Lazy.intercalate (eitherFormat formatter ", " ",")
|
||||||
. fmap f
|
. fmap f
|
||||||
|
|
||||||
bracketsCommas :: Formatter -> (a -> Text) -> [a] -> Text
|
bracketsCommas :: Formatter -> (a -> Text) -> [a] -> Text
|
||||||
bracketsCommas formatter f
|
bracketsCommas formatter f
|
||||||
= brackets
|
= brackets
|
||||||
. Text.intercalate (eitherFormat formatter ", " ",")
|
. Text.Lazy.intercalate (eitherFormat formatter ", " ",")
|
||||||
. fmap f
|
. fmap f
|
||||||
|
|
||||||
bracesList :: forall a. Formatter -> (a -> Text) -> [a] -> Text
|
bracesList :: forall a. Formatter -> (a -> Text) -> [a] -> Text
|
||||||
bracesList (Pretty intendation) f xs
|
bracesList (Pretty intendation) f xs
|
||||||
= Text.snoc (Text.intercalate "\n" content) '\n'
|
= Text.Lazy.snoc (Text.Lazy.intercalate "\n" content) '\n'
|
||||||
<> (Text.snoc $ Text.replicate (fromIntegral intendation) " ") '}'
|
<> (Text.Lazy.snoc $ Text.Lazy.replicate (fromIntegral intendation) " ") '}'
|
||||||
where
|
where
|
||||||
content = "{" : fmap f xs
|
content = "{" : fmap f xs
|
||||||
bracesList Minified f xs = braces $ Text.intercalate "," $ fmap f xs
|
bracesList Minified f xs = braces $ Text.Lazy.intercalate "," $ fmap f xs
|
||||||
|
|
||||||
optempty :: (Eq a, Monoid a, Monoid b) => (a -> b) -> a -> b
|
optempty :: (Eq a, Monoid a, Monoid b) => (a -> b) -> a -> b
|
||||||
optempty f xs = if xs == mempty then mempty else f xs
|
optempty f xs = if xs == mempty then mempty else f xs
|
||||||
|
@ -5,6 +5,7 @@ module Test.KitchenSinkSpec
|
|||||||
) where
|
) where
|
||||||
|
|
||||||
import qualified Data.Text.IO as Text.IO
|
import qualified Data.Text.IO as Text.IO
|
||||||
|
import qualified Data.Text.Lazy.IO as Text.Lazy.IO
|
||||||
import qualified Language.GraphQL.Encoder as Encoder
|
import qualified Language.GraphQL.Encoder as Encoder
|
||||||
import qualified Language.GraphQL.Parser as Parser
|
import qualified Language.GraphQL.Parser as Parser
|
||||||
import Paths_graphql (getDataFileName)
|
import Paths_graphql (getDataFileName)
|
||||||
@ -26,7 +27,7 @@ spec = describe "Kitchen Sink" $ do
|
|||||||
dataFileName <- getDataFileName "tests/data/kitchen-sink.graphql"
|
dataFileName <- getDataFileName "tests/data/kitchen-sink.graphql"
|
||||||
minFileName <- getDataFileName "tests/data/kitchen-sink.min.graphql"
|
minFileName <- getDataFileName "tests/data/kitchen-sink.min.graphql"
|
||||||
actual <- Text.IO.readFile dataFileName
|
actual <- Text.IO.readFile dataFileName
|
||||||
expected <- Text.IO.readFile minFileName
|
expected <- Text.Lazy.IO.readFile minFileName
|
||||||
|
|
||||||
either
|
either
|
||||||
(expectationFailure . errorBundlePretty)
|
(expectationFailure . errorBundlePretty)
|
||||||
|
Loading…
Reference in New Issue
Block a user