Replace AST.Selection data constructors

This commit is contained in:
2019-12-25 06:45:29 +01:00
parent bdf711d69f
commit 62f3c34bfe
7 changed files with 114 additions and 113 deletions

View File

@ -49,10 +49,11 @@ document formatter defs
| Pretty _ <- formatter = Lazy.Text.intercalate "\n" encodeDocument
| Minified <-formatter = Lazy.Text.snoc (mconcat encodeDocument) '\n'
where
encodeDocument = NonEmpty.toList $ definition formatter <$> defs
encodeDocument = foldr executableDefinition [] defs
executableDefinition (Full.ExecutableDefinition x) acc = definition formatter x : acc
-- | Converts a 'Full.Definition' into a string.
definition :: Formatter -> Full.Definition -> Lazy.Text
definition :: Formatter -> Full.ExecutableDefinition -> Lazy.Text
definition formatter x
| Pretty _ <- formatter = Lazy.Text.snoc (encodeDefinition x) '\n'
| Minified <- formatter = encodeDefinition x
@ -116,11 +117,12 @@ indent indentation = Lazy.Text.replicate (fromIntegral indentation) " "
selection :: Formatter -> Full.Selection -> Lazy.Text
selection formatter = Lazy.Text.append indent' . encodeSelection
where
encodeSelection (Full.SelectionField field') = field incrementIndent field'
encodeSelection (Full.SelectionInlineFragment fragment) =
inlineFragment incrementIndent fragment
encodeSelection (Full.SelectionFragmentSpread spread) =
fragmentSpread incrementIndent spread
encodeSelection (Full.Field alias name args directives' selections) =
field incrementIndent alias name args directives' selections
encodeSelection (Full.InlineFragment typeCondition directives' selections) =
inlineFragment incrementIndent typeCondition directives' selections
encodeSelection (Full.FragmentSpread name directives') =
fragmentSpread incrementIndent name directives'
incrementIndent
| Pretty indentation <- formatter = Pretty $ indentation + 1
| otherwise = Minified
@ -131,8 +133,14 @@ selection formatter = Lazy.Text.append indent' . encodeSelection
colon :: Formatter -> Lazy.Text
colon formatter = eitherFormat formatter ": " ":"
field :: Formatter -> Full.Field -> Lazy.Text
field formatter (Full.Field alias name args dirs set)
field :: Formatter ->
Maybe Full.Name ->
Full.Name ->
[Full.Argument] ->
[Full.Directive] ->
[Full.Selection] ->
Lazy.Text
field formatter alias name args dirs set
= optempty prependAlias (fold alias)
<> Lazy.Text.fromStrict name
<> optempty (arguments formatter) args
@ -154,13 +162,18 @@ argument formatter (Full.Argument name value')
-- * Fragments
fragmentSpread :: Formatter -> Full.FragmentSpread -> Lazy.Text
fragmentSpread formatter (Full.FragmentSpread name ds)
= "..." <> Lazy.Text.fromStrict name <> optempty (directives formatter) ds
fragmentSpread :: Formatter -> Full.Name -> [Full.Directive] -> Lazy.Text
fragmentSpread formatter name directives'
= "..." <> Lazy.Text.fromStrict name
<> optempty (directives formatter) directives'
inlineFragment :: Formatter -> Full.InlineFragment -> Lazy.Text
inlineFragment formatter (Full.InlineFragment tc dirs sels)
= "... on "
inlineFragment ::
Formatter ->
Maybe Full.TypeCondition ->
[Full.Directive] ->
Full.SelectionSet ->
Lazy.Text
inlineFragment formatter tc dirs sels = "... on "
<> Lazy.Text.fromStrict (fold tc)
<> directives formatter dirs
<> eitherFormat formatter " " mempty

View File

@ -134,7 +134,7 @@ braces = between (symbol "{") (symbol "}")
-- | Parser for strings.
string :: Parser T.Text
string = between "\"" "\"" stringValue <* spaceConsumer
string = between "\"" "\"" stringValue <* spaceConsumer
where
stringValue = T.pack <$> many stringCharacter
stringCharacter = satisfy isStringCharacter1
@ -143,7 +143,7 @@ string = between "\"" "\"" stringValue <* spaceConsumer
-- | Parser for block strings.
blockString :: Parser T.Text
blockString = between "\"\"\"" "\"\"\"" stringValue <* spaceConsumer
blockString = between "\"\"\"" "\"\"\"" stringValue <* spaceConsumer
where
stringValue = do
byLine <- sepBy (many blockStringCharacter) lineTerminator

View File

@ -6,23 +6,19 @@ module Language.GraphQL.AST.Parser
( document
) where
import Control.Applicative ( Alternative(..)
, optional
)
import Control.Applicative (Alternative(..), optional)
import Data.List.NonEmpty (NonEmpty(..))
import Language.GraphQL.AST
import Language.GraphQL.AST.Lexer
import Text.Megaparsec ( lookAhead
, option
, try
, (<?>)
)
import Text.Megaparsec (lookAhead, option, try, (<?>))
-- | Parser for the GraphQL documents.
document :: Parser Document
document = unicodeBOM >> spaceConsumer >> lexeme (manyNE definition)
document = unicodeBOM
>> spaceConsumer
>> lexeme (manyNE $ ExecutableDefinition <$> definition)
definition :: Parser Definition
definition :: Parser ExecutableDefinition
definition = DefinitionOperation <$> operationDefinition
<|> DefinitionFragment <$> fragmentDefinition
<?> "definition error!"
@ -50,19 +46,20 @@ selectionSetOpt :: Parser SelectionSetOpt
selectionSetOpt = braces $ some selection
selection :: Parser Selection
selection = SelectionField <$> field
<|> try (SelectionFragmentSpread <$> fragmentSpread)
<|> SelectionInlineFragment <$> inlineFragment
<?> "selection error!"
selection = field
<|> try fragmentSpread
<|> inlineFragment
<?> "selection error!"
-- * Field
field :: Parser Field
field = Field <$> optional alias
<*> name
<*> opt arguments
<*> opt directives
<*> opt selectionSetOpt
field :: Parser Selection
field = Field
<$> optional alias
<*> name
<*> opt arguments
<*> opt directives
<*> opt selectionSetOpt
alias :: Parser Alias
alias = try $ name <* colon
@ -77,16 +74,18 @@ argument = Argument <$> name <* colon <*> value
-- * Fragments
fragmentSpread :: Parser FragmentSpread
fragmentSpread = FragmentSpread <$ spread
<*> fragmentName
<*> opt directives
fragmentSpread :: Parser Selection
fragmentSpread = FragmentSpread
<$ spread
<*> fragmentName
<*> opt directives
inlineFragment :: Parser InlineFragment
inlineFragment = InlineFragment <$ spread
<*> optional typeCondition
<*> opt directives
<*> selectionSet
inlineFragment :: Parser Selection
inlineFragment = InlineFragment
<$ spread
<*> optional typeCondition
<*> opt directives
<*> selectionSet
fragmentDefinition :: Parser FragmentDefinition
fragmentDefinition = FragmentDefinition