{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
module Data.Morpheus.Parsing.Request.Selection
( parseSelectionSet
, parseFragmentDefinition
) where
import Data.Text (Text)
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.Request.Arguments (maybeArguments)
import Data.Morpheus.Types.Internal.AST.RawSelection (Fragment (..), RawArguments, RawSelection (..),
RawSelectionSet, Reference (..))
import Data.Morpheus.Types.Internal.AST.Selection (Selection (..))
parseSelectionSet :: Parser RawSelectionSet
parseSelectionSet = label "SelectionSet" $ setOf parseSelection
where
parseSelection = label "Selection" $
try inlineFragment
<|> try spread
<|> parseSelectionField
parseSelectionField :: Parser (Text, RawSelection)
parseSelectionField =
label "SelectionField" $ do
position <- getLocation
aliasName <- parseAlias
name <- parseName
arguments <- maybeArguments
_directives <- optionalDirectives
value <- selSet aliasName arguments <|> buildField aliasName arguments position
return (name, value)
where
buildField selectionAlias selectionArguments selectionPosition =
pure (RawSelectionField $ Selection { selectionAlias , selectionArguments, selectionRec = (), selectionPosition})
selSet :: Maybe Text -> RawArguments -> Parser RawSelection
selSet selectionAlias selectionArguments =
label "body" $ do
selectionPosition <- getLocation
selectionRec <- parseSelectionSet
return (RawSelectionSet $ Selection {selectionAlias , selectionArguments, selectionRec, selectionPosition})
spread :: Parser (Text, RawSelection)
spread =
label "FragmentSpread" $ do
referencePosition <- spreadLiteral
referenceName <- token
_directives <- optionalDirectives
return (referenceName, Spread $ Reference {referenceName, referencePosition})
parseFragmentDefinition :: Parser (Text, Fragment)
parseFragmentDefinition =
label "FragmentDefinition" $ do
keyword "fragment"
fragmentPosition <- getLocation
name <- parseName
fragmentType <- parseTypeCondition
_directives <- optionalDirectives
fragmentSelection <- parseSelectionSet
pure (name, Fragment {fragmentType, fragmentSelection, fragmentPosition})
inlineFragment :: Parser (Text, RawSelection)
inlineFragment =
label "InlineFragment" $ do
fragmentPosition <- spreadLiteral
fragmentType <- parseTypeCondition
_directives <- optionalDirectives
fragmentSelection <- parseSelectionSet
pure ("INLINE_FRAGMENT", InlineFragment $ Fragment {fragmentType, fragmentSelection, fragmentPosition})