{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Data.Morpheus.Parsing.Request.Selection
( parseSelectionSet
, parseFragmentDefinition
)
where
import Text.Megaparsec ( label
, try
, (<|>)
)
import Data.Morpheus.Parsing.Internal.Internal
( Parser
, getLocation
)
import Data.Morpheus.Parsing.Internal.Pattern
( optionalDirectives )
import Data.Morpheus.Parsing.Internal.Terms
( keyword
, parseAlias
, parseName
, parseTypeCondition
, setOf
, spreadLiteral
, token
)
import Data.Morpheus.Parsing.Internal.Arguments
( maybeArguments )
import Data.Morpheus.Types.Internal.AST
( Selection(..)
, SelectionContent(..)
, Ref(..)
, Fragment(..)
, Arguments
, RAW
, SelectionSet
, Name
, Position
)
parseSelectionSet :: Parser (SelectionSet RAW)
parseSelectionSet = label "SelectionSet" $ setOf parseSelection
where
parseSelection =
label "Selection"
$ try inlineFragment
<|> try spread
<|> parseSelectionField
parseSelectionField :: Parser (Selection RAW)
parseSelectionField = label "SelectionField" $ do
selectionPosition <- getLocation
selectionAlias <- parseAlias
selectionName <- parseName
selectionArguments <- maybeArguments
_directives <- optionalDirectives
selSet selectionName selectionAlias selectionArguments <|> pure Selection { selectionContent = SelectionField, ..}
where
selSet :: Name -> Maybe Name -> Arguments RAW -> Parser (Selection RAW)
selSet selectionName selectionAlias selectionArguments = label "body" $ do
selectionPosition <- getLocation
selectionSet <- parseSelectionSet
pure Selection { selectionContent = SelectionSet selectionSet, ..}
spread :: Parser (Selection RAW)
spread = label "FragmentSpread" $ do
refPosition <- spreadLiteral
refName <- token
_directives <- optionalDirectives
pure $ Spread Ref { .. }
parseFragmentDefinition :: Parser Fragment
parseFragmentDefinition = label "FragmentDefinition" $ do
keyword "fragment"
fragmentPosition <- getLocation
fragmentName <- parseName
fragmentBody fragmentName fragmentPosition
inlineFragment :: Parser (Selection RAW)
inlineFragment = label "InlineFragment" $ do
fragmentPosition <- spreadLiteral
InlineFragment <$> fragmentBody "INLINE_FRAGMENT" fragmentPosition
fragmentBody :: Name -> Position -> Parser Fragment
fragmentBody fragmentName fragmentPosition = label "FragmentBody" $ do
fragmentType <- parseTypeCondition
_directives <- optionalDirectives
fragmentSelection <- parseSelectionSet
pure $ Fragment { .. }