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

module Data.Morpheus.Parsing.Internal.Pattern
  ( inputValueDefinition,
    fieldsDefinition,
    typeDeclaration,
    optionalDirectives,
    enumValueDefinition,
    inputFieldsDefinition,
    parseOperationType,
    argumentsDefinition,
    parseDirectiveLocation,
  )
where

import Data.Morpheus.Parsing.Internal.Arguments
  ( maybeArguments,
  )
import Data.Morpheus.Parsing.Internal.Internal
  ( Parser,
    getLocation,
  )
import Data.Morpheus.Parsing.Internal.Terms
  ( at,
    colon,
    ignoredTokens,
    keyword,
    optDescription,
    parseName,
    parseType,
    parseTypeName,
    setOf,
    uniqTuple,
  )
import Data.Morpheus.Parsing.Internal.Value
  ( Parse (..),
    parseDefaultValue,
  )
import Data.Morpheus.Types.Internal.AST
  ( ArgumentsDefinition (..),
    DataEnumValue (..),
    Description,
    Directive (..),
    DirectiveLocation (..),
    FieldContent (..),
    FieldDefinition (..),
    FieldName,
    FieldsDefinition,
    IN,
    InputFieldsDefinition,
    OUT,
    OperationType (..),
    TRUE,
    TypeName,
    TypeRef,
    Value,
  )
import Relude hiding (many)
import Text.Megaparsec
  ( choice,
    label,
    many,
  )
import Text.Megaparsec.Byte (string)

--  EnumValueDefinition: https://graphql.github.io/graphql-spec/June2018/#EnumValueDefinition
--
--  EnumValueDefinition
--    Description(opt) EnumValue Directives(Const)(opt)
--
enumValueDefinition ::
  Parse (Value s) =>
  Parser (DataEnumValue s)
enumValueDefinition :: Parser (DataEnumValue s)
enumValueDefinition =
  String -> Parser (DataEnumValue s) -> Parser (DataEnumValue s)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"EnumValueDefinition" (Parser (DataEnumValue s) -> Parser (DataEnumValue s))
-> Parser (DataEnumValue s) -> Parser (DataEnumValue s)
forall a b. (a -> b) -> a -> b
$
    Maybe Description -> TypeName -> [Directive s] -> DataEnumValue s
forall (s :: Stage).
Maybe Description -> TypeName -> [Directive s] -> DataEnumValue s
DataEnumValue
      (Maybe Description -> TypeName -> [Directive s] -> DataEnumValue s)
-> ParsecT MyError ByteString Eventless (Maybe Description)
-> ParsecT
     MyError
     ByteString
     Eventless
     (TypeName -> [Directive s] -> DataEnumValue s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT MyError ByteString Eventless (Maybe Description)
optDescription
      ParsecT
  MyError
  ByteString
  Eventless
  (TypeName -> [Directive s] -> DataEnumValue s)
-> ParsecT MyError ByteString Eventless TypeName
-> ParsecT
     MyError ByteString Eventless ([Directive s] -> DataEnumValue s)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless TypeName
parseTypeName
      ParsecT
  MyError ByteString Eventless ([Directive s] -> DataEnumValue s)
-> ParsecT MyError ByteString Eventless [Directive s]
-> Parser (DataEnumValue s)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless [Directive s]
forall (s :: Stage). Parse (Value s) => Parser [Directive s]
optionalDirectives

-- InputValue : https://graphql.github.io/graphql-spec/June2018/#InputValueDefinition
--
-- InputValueDefinition
--   Description(opt) Name : Type DefaultValue(opt) Directives (Const)(opt)
--
inputValueDefinition ::
  Parse (Value s) =>
  Parser (FieldDefinition IN s)
inputValueDefinition :: Parser (FieldDefinition IN s)
inputValueDefinition =
  String
-> Parser (FieldDefinition IN s) -> Parser (FieldDefinition IN s)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"InputValueDefinition" (Parser (FieldDefinition IN s) -> Parser (FieldDefinition IN s))
-> Parser (FieldDefinition IN s) -> Parser (FieldDefinition IN s)
forall a b. (a -> b) -> a -> b
$
    Maybe Description
-> FieldName
-> TypeRef
-> Maybe (FieldContent TRUE IN s)
-> [Directive s]
-> FieldDefinition IN s
forall (cat :: TypeCategory) (s :: Stage).
Maybe Description
-> FieldName
-> TypeRef
-> Maybe (FieldContent TRUE cat s)
-> [Directive s]
-> FieldDefinition cat s
FieldDefinition
      (Maybe Description
 -> FieldName
 -> TypeRef
 -> Maybe (FieldContent TRUE IN s)
 -> [Directive s]
 -> FieldDefinition IN s)
-> ParsecT MyError ByteString Eventless (Maybe Description)
-> ParsecT
     MyError
     ByteString
     Eventless
     (FieldName
      -> TypeRef
      -> Maybe (FieldContent TRUE IN s)
      -> [Directive s]
      -> FieldDefinition IN s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT MyError ByteString Eventless (Maybe Description)
optDescription
      ParsecT
  MyError
  ByteString
  Eventless
  (FieldName
   -> TypeRef
   -> Maybe (FieldContent TRUE IN s)
   -> [Directive s]
   -> FieldDefinition IN s)
-> ParsecT MyError ByteString Eventless FieldName
-> ParsecT
     MyError
     ByteString
     Eventless
     (TypeRef
      -> Maybe (FieldContent TRUE IN s)
      -> [Directive s]
      -> FieldDefinition IN s)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless FieldName
parseName
      ParsecT
  MyError
  ByteString
  Eventless
  (TypeRef
   -> Maybe (FieldContent TRUE IN s)
   -> [Directive s]
   -> FieldDefinition IN s)
-> ParsecT MyError ByteString Eventless TypeRef
-> ParsecT
     MyError
     ByteString
     Eventless
     (Maybe (FieldContent TRUE IN s)
      -> [Directive s] -> FieldDefinition IN s)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser ()
colon Parser ()
-> ParsecT MyError ByteString Eventless TypeRef
-> ParsecT MyError ByteString Eventless TypeRef
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT MyError ByteString Eventless TypeRef
parseType)
      ParsecT
  MyError
  ByteString
  Eventless
  (Maybe (FieldContent TRUE IN s)
   -> [Directive s] -> FieldDefinition IN s)
-> ParsecT
     MyError ByteString Eventless (Maybe (FieldContent TRUE IN s))
-> ParsecT
     MyError
     ByteString
     Eventless
     ([Directive s] -> FieldDefinition IN s)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless (FieldContent TRUE IN s)
-> ParsecT
     MyError ByteString Eventless (Maybe (FieldContent TRUE IN s))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Value s -> FieldContent TRUE IN s
forall (s :: Stage) (cat :: TypeCategory).
Value s -> FieldContent (ELEM IN cat) cat s
DefaultInputValue (Value s -> FieldContent TRUE IN s)
-> ParsecT MyError ByteString Eventless (Value s)
-> ParsecT MyError ByteString Eventless (FieldContent TRUE IN s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT MyError ByteString Eventless (Value s)
forall (s :: Stage). Parser (Value s)
parseDefaultValue)
      ParsecT
  MyError
  ByteString
  Eventless
  ([Directive s] -> FieldDefinition IN s)
-> ParsecT MyError ByteString Eventless [Directive s]
-> Parser (FieldDefinition IN s)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless [Directive s]
forall (s :: Stage). Parse (Value s) => Parser [Directive s]
optionalDirectives

-- Field Arguments: https://graphql.github.io/graphql-spec/June2018/#sec-Field-Arguments
--
-- ArgumentsDefinition:
--   ( InputValueDefinition(list) )
--
argumentsDefinition ::
  Parse (Value s) =>
  Parser (ArgumentsDefinition s)
argumentsDefinition :: Parser (ArgumentsDefinition s)
argumentsDefinition =
  String
-> Parser (ArgumentsDefinition s) -> Parser (ArgumentsDefinition s)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"ArgumentsDefinition" (Parser (ArgumentsDefinition s) -> Parser (ArgumentsDefinition s))
-> Parser (ArgumentsDefinition s) -> Parser (ArgumentsDefinition s)
forall a b. (a -> b) -> a -> b
$
    Parser (FieldDefinition IN s) -> Parser (ArgumentsDefinition s)
forall a coll k.
(FromElems Eventless a coll, KeyOf k a) =>
Parser a -> Parser coll
uniqTuple Parser (FieldDefinition IN s)
forall (s :: Stage).
Parse (Value s) =>
Parser (FieldDefinition IN s)
inputValueDefinition

--  FieldsDefinition : https://graphql.github.io/graphql-spec/June2018/#FieldsDefinition
--
--  FieldsDefinition :
--    { FieldDefinition(list) }
--
fieldsDefinition ::
  Parse (Value s) =>
  Parser (FieldsDefinition OUT s)
fieldsDefinition :: Parser (FieldsDefinition OUT s)
fieldsDefinition = String
-> Parser (FieldsDefinition OUT s)
-> Parser (FieldsDefinition OUT s)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"FieldsDefinition" (Parser (FieldsDefinition OUT s)
 -> Parser (FieldsDefinition OUT s))
-> Parser (FieldsDefinition OUT s)
-> Parser (FieldsDefinition OUT s)
forall a b. (a -> b) -> a -> b
$ Parser (FieldDefinition OUT s) -> Parser (FieldsDefinition OUT s)
forall a coll k.
(FromElems Eventless a coll, KeyOf k a) =>
Parser a -> Parser coll
setOf Parser (FieldDefinition OUT s)
forall (s :: Stage).
Parse (Value s) =>
Parser (FieldDefinition OUT s)
fieldDefinition

--  FieldDefinition
--    Description(opt) Name ArgumentsDefinition(opt) : Type Directives(Const)(opt)
--
fieldDefinition :: Parse (Value s) => Parser (FieldDefinition OUT s)
fieldDefinition :: Parser (FieldDefinition OUT s)
fieldDefinition =
  String
-> Parser (FieldDefinition OUT s) -> Parser (FieldDefinition OUT s)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"FieldDefinition" (Parser (FieldDefinition OUT s) -> Parser (FieldDefinition OUT s))
-> Parser (FieldDefinition OUT s) -> Parser (FieldDefinition OUT s)
forall a b. (a -> b) -> a -> b
$
    Maybe Description
-> FieldName
-> Maybe (FieldContent TRUE OUT s)
-> TypeRef
-> [Directive s]
-> FieldDefinition OUT s
forall (cat :: TypeCategory) (s :: Stage).
Maybe Description
-> FieldName
-> Maybe (FieldContent TRUE cat s)
-> TypeRef
-> [Directive s]
-> FieldDefinition cat s
mkField
      (Maybe Description
 -> FieldName
 -> Maybe (FieldContent TRUE OUT s)
 -> TypeRef
 -> [Directive s]
 -> FieldDefinition OUT s)
-> ParsecT MyError ByteString Eventless (Maybe Description)
-> ParsecT
     MyError
     ByteString
     Eventless
     (FieldName
      -> Maybe (FieldContent TRUE OUT s)
      -> TypeRef
      -> [Directive s]
      -> FieldDefinition OUT s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT MyError ByteString Eventless (Maybe Description)
optDescription
      ParsecT
  MyError
  ByteString
  Eventless
  (FieldName
   -> Maybe (FieldContent TRUE OUT s)
   -> TypeRef
   -> [Directive s]
   -> FieldDefinition OUT s)
-> ParsecT MyError ByteString Eventless FieldName
-> ParsecT
     MyError
     ByteString
     Eventless
     (Maybe (FieldContent TRUE OUT s)
      -> TypeRef -> [Directive s] -> FieldDefinition OUT s)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless FieldName
parseName
      ParsecT
  MyError
  ByteString
  Eventless
  (Maybe (FieldContent TRUE OUT s)
   -> TypeRef -> [Directive s] -> FieldDefinition OUT s)
-> ParsecT
     MyError ByteString Eventless (Maybe (FieldContent TRUE OUT s))
-> ParsecT
     MyError
     ByteString
     Eventless
     (TypeRef -> [Directive s] -> FieldDefinition OUT s)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless (FieldContent TRUE OUT s)
-> ParsecT
     MyError ByteString Eventless (Maybe (FieldContent TRUE OUT s))
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (ArgumentsDefinition s -> FieldContent TRUE OUT s
forall (s :: Stage) (cat :: TypeCategory).
ArgumentsDefinition s -> FieldContent (ELEM OUT cat) cat s
FieldArgs (ArgumentsDefinition s -> FieldContent TRUE OUT s)
-> ParsecT MyError ByteString Eventless (ArgumentsDefinition s)
-> ParsecT MyError ByteString Eventless (FieldContent TRUE OUT s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT MyError ByteString Eventless (ArgumentsDefinition s)
forall (s :: Stage).
Parse (Value s) =>
Parser (ArgumentsDefinition s)
argumentsDefinition)
      ParsecT
  MyError
  ByteString
  Eventless
  (TypeRef -> [Directive s] -> FieldDefinition OUT s)
-> ParsecT MyError ByteString Eventless TypeRef
-> ParsecT
     MyError
     ByteString
     Eventless
     ([Directive s] -> FieldDefinition OUT s)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser ()
colon Parser ()
-> ParsecT MyError ByteString Eventless TypeRef
-> ParsecT MyError ByteString Eventless TypeRef
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT MyError ByteString Eventless TypeRef
parseType)
      ParsecT
  MyError
  ByteString
  Eventless
  ([Directive s] -> FieldDefinition OUT s)
-> ParsecT MyError ByteString Eventless [Directive s]
-> Parser (FieldDefinition OUT s)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless [Directive s]
forall (s :: Stage). Parse (Value s) => Parser [Directive s]
optionalDirectives

mkField ::
  Maybe Description ->
  FieldName ->
  Maybe (FieldContent TRUE cat s) ->
  TypeRef ->
  [Directive s] ->
  FieldDefinition cat s
mkField :: Maybe Description
-> FieldName
-> Maybe (FieldContent TRUE cat s)
-> TypeRef
-> [Directive s]
-> FieldDefinition cat s
mkField Maybe Description
fieldDescription FieldName
fieldName Maybe (FieldContent TRUE cat s)
fieldContent TypeRef
fieldType [Directive s]
fieldDirectives =
  FieldDefinition :: forall (cat :: TypeCategory) (s :: Stage).
Maybe Description
-> FieldName
-> TypeRef
-> Maybe (FieldContent TRUE cat s)
-> [Directive s]
-> FieldDefinition cat s
FieldDefinition {[Directive s]
Maybe Description
Maybe (FieldContent TRUE cat s)
TypeRef
FieldName
fieldDirectives :: [Directive s]
fieldContent :: Maybe (FieldContent TRUE cat s)
fieldType :: TypeRef
fieldName :: FieldName
fieldDescription :: Maybe Description
fieldDirectives :: [Directive s]
fieldType :: TypeRef
fieldContent :: Maybe (FieldContent TRUE cat s)
fieldName :: FieldName
fieldDescription :: Maybe Description
..}

-- InputFieldsDefinition : https://graphql.github.io/graphql-spec/June2018/#sec-Language.Directives
--   InputFieldsDefinition:
--     { InputValueDefinition(list) }
--
inputFieldsDefinition ::
  Parse (Value s) =>
  Parser (InputFieldsDefinition s)
inputFieldsDefinition :: Parser (InputFieldsDefinition s)
inputFieldsDefinition = String
-> Parser (InputFieldsDefinition s)
-> Parser (InputFieldsDefinition s)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"InputFieldsDefinition" (Parser (InputFieldsDefinition s)
 -> Parser (InputFieldsDefinition s))
-> Parser (InputFieldsDefinition s)
-> Parser (InputFieldsDefinition s)
forall a b. (a -> b) -> a -> b
$ Parser (FieldDefinition IN s) -> Parser (InputFieldsDefinition s)
forall a coll k.
(FromElems Eventless a coll, KeyOf k a) =>
Parser a -> Parser coll
setOf Parser (FieldDefinition IN s)
forall (s :: Stage).
Parse (Value s) =>
Parser (FieldDefinition IN s)
inputValueDefinition

-- Directives : https://graphql.github.io/graphql-spec/June2018/#sec-Language.Directives
--
-- example: @directive ( arg1: "value" , .... )
--
-- Directives[Const]
-- Directive[Const](list)
--
optionalDirectives :: Parse (Value s) => Parser [Directive s]
optionalDirectives :: Parser [Directive s]
optionalDirectives = String -> Parser [Directive s] -> Parser [Directive s]
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"Directives" (Parser [Directive s] -> Parser [Directive s])
-> Parser [Directive s] -> Parser [Directive s]
forall a b. (a -> b) -> a -> b
$ ParsecT MyError ByteString Eventless (Directive s)
-> Parser [Directive s]
forall (m :: * -> *) a. MonadPlus m => m a -> m [a]
many ParsecT MyError ByteString Eventless (Directive s)
forall (s :: Stage). Parse (Value s) => Parser (Directive s)
directive

-- Directive[Const]
--
-- @ Name Arguments[Const](opt)
directive :: Parse (Value s) => Parser (Directive s)
directive :: Parser (Directive s)
directive =
  String -> Parser (Directive s) -> Parser (Directive s)
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"Directive" (Parser (Directive s) -> Parser (Directive s))
-> Parser (Directive s) -> Parser (Directive s)
forall a b. (a -> b) -> a -> b
$
    Position -> FieldName -> Arguments s -> Directive s
forall (s :: Stage).
Position -> FieldName -> Arguments s -> Directive s
Directive
      (Position -> FieldName -> Arguments s -> Directive s)
-> ParsecT MyError ByteString Eventless Position
-> ParsecT
     MyError
     ByteString
     Eventless
     (FieldName -> Arguments s -> Directive s)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ParsecT MyError ByteString Eventless Position
getLocation
      ParsecT
  MyError
  ByteString
  Eventless
  (FieldName -> Arguments s -> Directive s)
-> ParsecT MyError ByteString Eventless FieldName
-> ParsecT
     MyError ByteString Eventless (Arguments s -> Directive s)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Parser ()
at Parser ()
-> ParsecT MyError ByteString Eventless FieldName
-> ParsecT MyError ByteString Eventless FieldName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT MyError ByteString Eventless FieldName
parseName)
      ParsecT MyError ByteString Eventless (Arguments s -> Directive s)
-> ParsecT MyError ByteString Eventless (Arguments s)
-> Parser (Directive s)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> ParsecT MyError ByteString Eventless (Arguments s)
forall (s :: Stage). Parse (Value s) => Parser (Arguments s)
maybeArguments

-- typDeclaration : Not in spec ,start part of type definitions
--
--  typDeclaration
--   Description(opt) scalar Name
--
typeDeclaration :: FieldName -> Parser TypeName
typeDeclaration :: FieldName -> ParsecT MyError ByteString Eventless TypeName
typeDeclaration FieldName
kind = FieldName -> Parser ()
keyword FieldName
kind Parser ()
-> ParsecT MyError ByteString Eventless TypeName
-> ParsecT MyError ByteString Eventless TypeName
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT MyError ByteString Eventless TypeName
parseTypeName

parseOperationType :: Parser OperationType
parseOperationType :: Parser OperationType
parseOperationType =
  String -> Parser OperationType -> Parser OperationType
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label String
"OperationType" (Parser OperationType -> Parser OperationType)
-> Parser OperationType -> Parser OperationType
forall a b. (a -> b) -> a -> b
$
    ( (Tokens ByteString
-> ParsecT MyError ByteString Eventless (Tokens ByteString)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens ByteString
"query" ParsecT MyError ByteString Eventless ByteString
-> OperationType -> Parser OperationType
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> OperationType
Query)
        Parser OperationType
-> Parser OperationType -> Parser OperationType
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Tokens ByteString
-> ParsecT MyError ByteString Eventless (Tokens ByteString)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens ByteString
"mutation" ParsecT MyError ByteString Eventless ByteString
-> OperationType -> Parser OperationType
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> OperationType
Mutation)
        Parser OperationType
-> Parser OperationType -> Parser OperationType
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Tokens ByteString
-> ParsecT MyError ByteString Eventless (Tokens ByteString)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string Tokens ByteString
"subscription" ParsecT MyError ByteString Eventless ByteString
-> OperationType -> Parser OperationType
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> OperationType
Subscription)
    )
      Parser OperationType -> Parser () -> Parser OperationType
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
ignoredTokens

parseDirectiveLocation :: Parser DirectiveLocation
parseDirectiveLocation :: Parser DirectiveLocation
parseDirectiveLocation =
  String -> Parser DirectiveLocation -> Parser DirectiveLocation
forall e s (m :: * -> *) a.
MonadParsec e s m =>
String -> m a -> m a
label
    String
"DirectiveLocation"
    ( [Parser DirectiveLocation] -> Parser DirectiveLocation
forall (f :: * -> *) (m :: * -> *) a.
(Foldable f, Alternative m) =>
f (m a) -> m a
choice ([Parser DirectiveLocation] -> Parser DirectiveLocation)
-> [Parser DirectiveLocation] -> Parser DirectiveLocation
forall a b. (a -> b) -> a -> b
$
        DirectiveLocation -> Parser DirectiveLocation
forall a. Show a => a -> Parser a
toKeyword
          (DirectiveLocation -> Parser DirectiveLocation)
-> [DirectiveLocation] -> [Parser DirectiveLocation]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [ DirectiveLocation
FIELD_DEFINITION,
                DirectiveLocation
FRAGMENT_DEFINITION,
                DirectiveLocation
FRAGMENT_SPREAD,
                DirectiveLocation
INLINE_FRAGMENT,
                DirectiveLocation
ARGUMENT_DEFINITION,
                DirectiveLocation
INTERFACE,
                DirectiveLocation
ENUM_VALUE,
                DirectiveLocation
INPUT_OBJECT,
                DirectiveLocation
INPUT_FIELD_DEFINITION,
                DirectiveLocation
SCHEMA,
                DirectiveLocation
SCALAR,
                DirectiveLocation
OBJECT,
                DirectiveLocation
QUERY,
                DirectiveLocation
MUTATION,
                DirectiveLocation
SUBSCRIPTION,
                DirectiveLocation
UNION,
                DirectiveLocation
ENUM,
                DirectiveLocation
FIELD
              ]
    )
    Parser DirectiveLocation -> Parser () -> Parser DirectiveLocation
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a
<* Parser ()
ignoredTokens

toKeyword :: Show a => a -> Parser a
toKeyword :: a -> Parser a
toKeyword a
x = Tokens ByteString
-> ParsecT MyError ByteString Eventless (Tokens ByteString)
forall e s (m :: * -> *).
MonadParsec e s m =>
Tokens s -> m (Tokens s)
string (String -> ByteString
forall a. IsString a => String -> a
fromString (String -> ByteString) -> String -> ByteString
forall a b. (a -> b) -> a -> b
$ a -> String
forall b a. (Show a, IsString b) => a -> b
show a
x) ParsecT MyError ByteString Eventless ByteString -> a -> Parser a
forall (f :: * -> *) a b. Functor f => f a -> b -> f b
$> a
x