{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Data.Morpheus.Parsing.Request.Operation
  ( parseOperation,
  )
where

import Data.Morpheus.Internal.Utils
  ( empty,
  )
import Data.Morpheus.Parsing.Internal.Internal
  ( Parser,
    getLocation,
  )
import Data.Morpheus.Parsing.Internal.Pattern
  ( optionalDirectives,
    parseOperationType,
  )
import Data.Morpheus.Parsing.Internal.Terms
  ( colon,
    parseName,
    parseType,
    uniqTupleOpt,
    varName,
  )
import Data.Morpheus.Parsing.Internal.Value
  ( parseDefaultValue,
  )
import Data.Morpheus.Parsing.Request.Selection
  ( parseSelectionSet,
  )
import Data.Morpheus.Types.Internal.AST
  ( Operation (..),
    OperationType (..),
    RAW,
    Variable (..),
    VariableContent (..),
  )
import Relude hiding (empty)
import Text.Megaparsec
  ( label,
    (<?>),
  )

-- Variables :  https://graphql.github.io/graphql-spec/June2018/#VariableDefinition
--
--  VariableDefinition
--    Variable : Type DefaultValue(opt)
--
variableDefinition :: Parser (Variable RAW)
variableDefinition :: Parser (Variable RAW)
variableDefinition =
  forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"VariableDefinition" forall a b. (a -> b) -> a -> b
$
    forall (stage :: Stage).
Position
-> FieldName
-> TypeRef
-> VariableContent (CONST_OR_VALID stage)
-> Variable stage
Variable
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Position
getLocation
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ParsecT Void ByteString GQLResult FieldName
varName forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
colon)
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser TypeRef
parseType
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Maybe ResolvedValue -> VariableContent 'CONST
DefaultValue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall (s :: Stage). Parser (Value s)
parseDefaultValue)

-- Operations : https://graphql.github.io/graphql-spec/June2018/#sec-Language.Operations
--
-- OperationDefinition
--   OperationType Name(opt) VariableDefinitions(opt) Directives(opt) SelectionSet
--
--   OperationType: one of
--     query, mutation,    subscription
parseOperationDefinition :: Parser (Operation RAW)
parseOperationDefinition :: Parser (Operation RAW)
parseOperationDefinition =
  forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"OperationDefinition" forall a b. (a -> b) -> a -> b
$
    forall (s :: Stage).
Position
-> OperationType
-> Maybe FieldName
-> VariableDefinitions s
-> Directives s
-> SelectionSet s
-> Operation s
Operation
      forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Parser Position
getLocation
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser OperationType
parseOperationType
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional forall (t :: NAME). Parser (Name t)
parseName
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (map :: * -> * -> *) k a.
(FromList GQLResult map k a, Empty (map k a), KeyOf k a) =>
Parser a -> Parser (map k a)
uniqTupleOpt Parser (Variable RAW)
variableDefinition
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (s :: Stage). Parse (Value s) => Parser (Directives s)
optionalDirectives
      forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (SelectionSet RAW)
parseSelectionSet

parseAnonymousQuery :: Parser (Operation RAW)
parseAnonymousQuery :: Parser (Operation RAW)
parseAnonymousQuery = forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"AnonymousQuery" forall a b. (a -> b) -> a -> b
$ do
  Position
operationPosition <- Parser Position
getLocation
  MergeMap 'True FieldName (Selection RAW)
operationSelection <- Parser (SelectionSet RAW)
parseSelectionSet
  forall (f :: * -> *) a. Applicative f => a -> f a
pure
    ( Operation
        { operationName :: Maybe FieldName
operationName = forall a. Maybe a
Nothing,
          operationType :: OperationType
operationType = OperationType
Query,
          operationArguments :: VariableDefinitions RAW
operationArguments = forall coll. Empty coll => coll
empty,
          operationDirectives :: Directives RAW
operationDirectives = forall coll. Empty coll => coll
empty,
          MergeMap 'True FieldName (Selection RAW)
Position
operationSelection :: SelectionSet RAW
operationPosition :: Position
operationSelection :: MergeMap 'True FieldName (Selection RAW)
operationPosition :: Position
..
        }
    )
    forall e s (m :: * -> *) a.
MonadParsec e s m =>
m a -> String -> m a
<?> String
"can't parse AnonymousQuery"

parseOperation :: Parser (Operation RAW)
parseOperation :: Parser (Operation RAW)
parseOperation = Parser (Operation RAW)
parseAnonymousQuery forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser (Operation RAW)
parseOperationDefinition