{-# 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 =
  String -> Parser (Variable RAW) -> Parser (Variable RAW)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"VariableDefinition" (Parser (Variable RAW) -> Parser (Variable RAW))
-> Parser (Variable RAW) -> Parser (Variable RAW)
forall a b. (a -> b) -> a -> b
$
    Position
-> FieldName -> TypeRef -> VariableContent CONST -> Variable RAW
forall (stage :: Stage).
Position
-> FieldName
-> TypeRef
-> VariableContent (CONST_OR_VALID stage)
-> Variable stage
Variable
      (Position
 -> FieldName -> TypeRef -> VariableContent CONST -> Variable RAW)
-> ParsecT MyError ByteString Eventless Position
-> ParsecT
     MyError
     ByteString
     Eventless
     (FieldName -> TypeRef -> VariableContent CONST -> Variable RAW)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT MyError ByteString Eventless Position
getLocation
      ParsecT
  MyError
  ByteString
  Eventless
  (FieldName -> TypeRef -> VariableContent CONST -> Variable RAW)
-> ParsecT MyError ByteString Eventless FieldName
-> ParsecT
     MyError
     ByteString
     Eventless
     (TypeRef -> VariableContent CONST -> Variable RAW)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (ParsecT MyError ByteString Eventless FieldName
varName ParsecT MyError ByteString Eventless FieldName
-> ParsecT MyError ByteString Eventless ()
-> ParsecT MyError ByteString Eventless FieldName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* ParsecT MyError ByteString Eventless ()
colon)
      ParsecT
  MyError
  ByteString
  Eventless
  (TypeRef -> VariableContent CONST -> Variable RAW)
-> ParsecT MyError ByteString Eventless TypeRef
-> ParsecT
     MyError
     ByteString
     Eventless
     (VariableContent CONST -> Variable RAW)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless TypeRef
parseType
      ParsecT
  MyError
  ByteString
  Eventless
  (VariableContent CONST -> Variable RAW)
-> ParsecT MyError ByteString Eventless (VariableContent CONST)
-> Parser (Variable RAW)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Maybe ResolvedValue -> VariableContent CONST
DefaultValue (Maybe ResolvedValue -> VariableContent CONST)
-> ParsecT MyError ByteString Eventless (Maybe ResolvedValue)
-> ParsecT MyError ByteString Eventless (VariableContent CONST)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT MyError ByteString Eventless ResolvedValue
-> ParsecT MyError ByteString Eventless (Maybe ResolvedValue)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT MyError ByteString Eventless ResolvedValue
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 =
  String -> Parser (Operation RAW) -> Parser (Operation RAW)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"OperationDefinition" (Parser (Operation RAW) -> Parser (Operation RAW))
-> Parser (Operation RAW) -> Parser (Operation RAW)
forall a b. (a -> b) -> a -> b
$
    Position
-> OperationType
-> Maybe FieldName
-> VariableDefinitions RAW
-> Directives RAW
-> SelectionSet RAW
-> Operation RAW
forall (s :: Stage).
Position
-> OperationType
-> Maybe FieldName
-> VariableDefinitions s
-> Directives s
-> SelectionSet s
-> Operation s
Operation
      (Position
 -> OperationType
 -> Maybe FieldName
 -> VariableDefinitions RAW
 -> Directives RAW
 -> SelectionSet RAW
 -> Operation RAW)
-> ParsecT MyError ByteString Eventless Position
-> ParsecT
     MyError
     ByteString
     Eventless
     (OperationType
      -> Maybe FieldName
      -> VariableDefinitions RAW
      -> Directives RAW
      -> SelectionSet RAW
      -> Operation RAW)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT MyError ByteString Eventless Position
getLocation
      ParsecT
  MyError
  ByteString
  Eventless
  (OperationType
   -> Maybe FieldName
   -> VariableDefinitions RAW
   -> Directives RAW
   -> SelectionSet RAW
   -> Operation RAW)
-> ParsecT MyError ByteString Eventless OperationType
-> ParsecT
     MyError
     ByteString
     Eventless
     (Maybe FieldName
      -> VariableDefinitions RAW
      -> Directives RAW
      -> SelectionSet RAW
      -> Operation RAW)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless OperationType
parseOperationType
      ParsecT
  MyError
  ByteString
  Eventless
  (Maybe FieldName
   -> VariableDefinitions RAW
   -> Directives RAW
   -> SelectionSet RAW
   -> Operation RAW)
-> ParsecT MyError ByteString Eventless (Maybe FieldName)
-> ParsecT
     MyError
     ByteString
     Eventless
     (VariableDefinitions RAW
      -> Directives RAW -> SelectionSet RAW -> Operation RAW)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless FieldName
-> ParsecT MyError ByteString Eventless (Maybe FieldName)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional ParsecT MyError ByteString Eventless FieldName
parseName
      ParsecT
  MyError
  ByteString
  Eventless
  (VariableDefinitions RAW
   -> Directives RAW -> SelectionSet RAW -> Operation RAW)
-> ParsecT MyError ByteString Eventless (VariableDefinitions RAW)
-> ParsecT
     MyError
     ByteString
     Eventless
     (Directives RAW -> SelectionSet RAW -> Operation RAW)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> Parser (Variable RAW)
-> ParsecT MyError ByteString Eventless (VariableDefinitions RAW)
forall a coll k.
(FromElems Eventless a coll, Collection a coll, KeyOf k a) =>
Parser a -> Parser coll
uniqTupleOpt Parser (Variable RAW)
variableDefinition
      ParsecT
  MyError
  ByteString
  Eventless
  (Directives RAW -> SelectionSet RAW -> Operation RAW)
-> ParsecT MyError ByteString Eventless (Directives RAW)
-> ParsecT
     MyError ByteString Eventless (SelectionSet RAW -> Operation RAW)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless (Directives RAW)
forall (s :: Stage). Parse (Value s) => Parser [Directive s]
optionalDirectives
      ParsecT
  MyError ByteString Eventless (SelectionSet RAW -> Operation RAW)
-> ParsecT MyError ByteString Eventless (SelectionSet RAW)
-> Parser (Operation RAW)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless (SelectionSet RAW)
parseSelectionSet

parseAnonymousQuery :: Parser (Operation RAW)
parseAnonymousQuery :: Parser (Operation RAW)
parseAnonymousQuery = String -> Parser (Operation RAW) -> Parser (Operation RAW)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"AnonymousQuery" (Parser (Operation RAW) -> Parser (Operation RAW))
-> Parser (Operation RAW) -> Parser (Operation RAW)
forall a b. (a -> b) -> a -> b
$ do
  Position
operationPosition <- ParsecT MyError ByteString Eventless Position
getLocation
  SelectionSet RAW
operationSelection <- ParsecT MyError ByteString Eventless (SelectionSet RAW)
parseSelectionSet
  Operation RAW -> Parser (Operation RAW)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
    ( Operation :: forall (s :: Stage).
Position
-> OperationType
-> Maybe FieldName
-> VariableDefinitions s
-> Directives s
-> SelectionSet s
-> Operation s
Operation
        { operationName :: Maybe FieldName
operationName = Maybe FieldName
forall a. Maybe a
Nothing,
          operationType :: OperationType
operationType = OperationType
Query,
          operationArguments :: VariableDefinitions RAW
operationArguments = VariableDefinitions RAW
forall a coll. Collection a coll => coll
empty,
          operationDirectives :: Directives RAW
operationDirectives = Directives RAW
forall a coll. Collection a coll => coll
empty,
          Position
SelectionSet RAW
operationSelection :: SelectionSet RAW
operationPosition :: Position
operationSelection :: SelectionSet RAW
operationPosition :: Position
..
        }
    )
    Parser (Operation RAW) -> String -> Parser (Operation RAW)
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 Parser (Operation RAW)
-> Parser (Operation RAW) -> Parser (Operation RAW)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Parser (Operation RAW)
parseOperationDefinition