Test the encoder with the unminified document

This commit is contained in:
Eugen Wissner 2019-07-27 07:19:21 +02:00
parent 15568a3b99
commit d690d22ce8
4 changed files with 37 additions and 21 deletions

View File

@ -4,11 +4,15 @@ All notable changes to this project will be documented in this file.
## [Unreleased] ## [Unreleased]
### Added ### Added
- `executeWithName` executes an operation with the given name. - `executeWithName` executes an operation with the given name.
- Export `Language.GraphQL.Encoder.definition`.
### Changed ### Changed
- `Operation` includes now possible operation name which allows to support - `Operation` includes now possible operation name which allows to support
documents with multiple operations. documents with multiple operations.
### Removed
- Unused `Language.GraphQL.Encoder.spaced`.
## [0.4.0.0] - 2019-07-23 ## [0.4.0.0] - 2019-07-23
### Added ### Added
- Support for mutations. - Support for mutations.

View File

@ -1,24 +1,31 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
-- | This module defines a printer for the @GraphQL@ language. -- | This module defines a printer for the @GraphQL@ language.
module Language.GraphQL.Encoder module Language.GraphQL.Encoder
( document ( definition
, spaced , document
) where ) where
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, cons, intercalate, pack, snoc) import Data.Text (Text, pack)
import qualified Data.Text as Text
import Language.GraphQL.AST import Language.GraphQL.AST
-- * Document -- | Converts a 'Document' into a string.
document :: Document -> Text document :: Document -> Text
document defs = (`snoc` '\n') . mconcat . NonEmpty.toList $ definition <$> defs document defs = Text.intercalate "\n"
. NonEmpty.toList
$ definition <$> defs
-- | Converts a 'Definition' into a string.
definition :: Definition -> Text definition :: Definition -> Text
definition (DefinitionOperation x) = operationDefinition x definition x = Text.snoc (encodeDefinition x) '\n'
definition (DefinitionFragment x) = fragmentDefinition x where
encodeDefinition (DefinitionOperation operation)
= operationDefinition operation
encodeDefinition (DefinitionFragment fragment)
= fragmentDefinition fragment
operationDefinition :: OperationDefinition -> Text operationDefinition :: OperationDefinition -> Text
operationDefinition (OperationSelectionSet sels) = selectionSet sels operationDefinition (OperationSelectionSet sels) = selectionSet sels
@ -60,7 +67,7 @@ selection (SelectionFragmentSpread x) = fragmentSpread x
field :: Field -> Text field :: Field -> Text
field (Field alias name args dirs selso) = field (Field alias name args dirs selso) =
optempty (`snoc` ':') (fold alias) optempty (`Text.snoc` ':') (fold alias)
<> name <> name
<> optempty arguments args <> optempty arguments args
<> optempty directives dirs <> optempty directives dirs
@ -146,11 +153,8 @@ nonNullType (NonNullTypeList x) = listType x <> "!"
-- * Internal -- * Internal
spaced :: Text -> Text
spaced = cons '\SP'
between :: Char -> Char -> Text -> Text between :: Char -> Char -> Text -> Text
between open close = cons open . (`snoc` close) between open close = Text.cons open . (`Text.snoc` close)
parens :: Text -> Text parens :: Text -> Text
parens = between '(' ')' parens = between '(' ')'
@ -165,16 +169,16 @@ quotes :: Text -> Text
quotes = between '"' '"' quotes = between '"' '"'
spaces :: (a -> Text) -> [a] -> Text spaces :: (a -> Text) -> [a] -> Text
spaces f = intercalate "\SP" . fmap f spaces f = Text.intercalate "\SP" . fmap f
parensCommas :: (a -> Text) -> [a] -> Text parensCommas :: (a -> Text) -> [a] -> Text
parensCommas f = parens . intercalate "," . fmap f parensCommas f = parens . Text.intercalate "," . fmap f
bracketsCommas :: (a -> Text) -> [a] -> Text bracketsCommas :: (a -> Text) -> [a] -> Text
bracketsCommas f = brackets . intercalate "," . fmap f bracketsCommas f = brackets . Text.intercalate "," . fmap f
bracesCommas :: (a -> Text) -> [a] -> Text bracesCommas :: (a -> Text) -> [a] -> Text
bracesCommas f = braces . intercalate "," . fmap f bracesCommas f = braces . Text.intercalate "," . fmap f
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

View File

@ -20,10 +20,12 @@ import Text.Megaparsec ( errorBundlePretty
spec :: Spec spec :: Spec
spec = describe "Kitchen Sink" $ spec = describe "Kitchen Sink" $
it "prints the query" $ do it "prints the query" $ do
dataFileName <- getDataFileName "tests/data/kitchen-sink.min.graphql" dataFileName <- getDataFileName "tests/data/kitchen-sink.graphql"
expected <- Text.IO.readFile dataFileName minFileName <- getDataFileName "tests/data/kitchen-sink.min.graphql"
actual <- Text.IO.readFile dataFileName
expected <- Text.IO.readFile minFileName
either either
(expectationFailure . errorBundlePretty) (expectationFailure . errorBundlePretty)
(flip shouldBe expected . Encoder.document) (flip shouldBe expected . Encoder.document)
$ parse Parser.document dataFileName expected $ parse Parser.document dataFileName actual

View File

@ -1 +1,7 @@
query queryName($foo:ComplexType,$site:Site=MOBILE){whoever123is:node(id:[123,456]){id,... on User@defer{field2{id,alias:field1(first:10,after:$foo)@include(if:$foo){id,...frag}}}}}mutation likeStory{like(story:123)@defer{story{id}}}fragment frag on Friend{foo(size:$size,bar:$b,obj:{key:"value"})} query queryName($foo:ComplexType,$site:Site=MOBILE){whoever123is:node(id:[123,456]){id,... on User@defer{field2{id,alias:field1(first:10,after:$foo)@include(if:$foo){id,...frag}}}}}
mutation likeStory{like(story:123)@defer{story{id}}}
fragment frag on Friend{foo(size:$size,bar:$b,obj:{key:"value"})}
{unnamed(truthy:true,falsey:false),query}