{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Data.Morpheus.Server.Deriving.Schema.Directive
  ( deriveFieldDirectives,
    deriveTypeDirectives,
    deriveEnumDirectives,
    visitEnumValueDescription,
    visitFieldDescription,
    visitTypeDescription,
    visitFieldDefaultValue,
    visitFieldContent,
    visitEnumName,
    visitFieldName,
    toFieldRes,
    UseDirective (..),
  )
where

import qualified Data.HashMap.Lazy as HM
import Data.Morpheus.Internal.Ext (unsafeFromList)
import Data.Morpheus.Internal.Utils (Empty (..), fromElems)
import Data.Morpheus.Server.Deriving.Utils.Kinded
  ( CatType (..),
    KindedProxy (..),
  )
import Data.Morpheus.Server.Deriving.Utils.Types (FieldRep (..))
import Data.Morpheus.Server.Deriving.Utils.Use
  ( UseArguments (..),
    UseDirective (..),
    UseGQLType (..),
  )
import Data.Morpheus.Server.Types.Directives
  ( GDirectiveUsage (..),
    GDirectiveUsages (..),
    GQLDirective (..),
    applyEnumDescription,
    applyEnumName,
    applyFieldDefaultValue,
    applyFieldDescription,
    applyFieldName,
    applyTypeDescription,
    applyTypeEnumNames,
    applyTypeFieldNames,
    getLocations,
  )
import Data.Morpheus.Server.Types.SchemaT
  ( SchemaT,
    insertDirectiveDefinition,
    outToAny,
  )
import Data.Morpheus.Types.Internal.AST
  ( Argument (..),
    CONST,
    Description,
    Directive (..),
    DirectiveDefinition (..),
    Directives,
    FieldContent (..),
    FieldName,
    IN,
    Position (Position),
    TRUE,
    TypeCategory (..),
    TypeName,
    Value,
  )
import GHC.Generics ()
import GHC.TypeLits ()
import Relude hiding (empty)

deriveDirectiveDefinition ::
  forall a b kind gql args.
  (gql a, GQLDirective a, args a) =>
  UseDirective gql args ->
  a ->
  b ->
  SchemaT kind (DirectiveDefinition CONST)
deriveDirectiveDefinition :: forall a b (kind :: TypeCategory) (gql :: * -> Constraint)
       (args :: * -> Constraint).
(gql a, GQLDirective a, args a) =>
UseDirective gql args
-> a -> b -> SchemaT kind (DirectiveDefinition CONST)
deriveDirectiveDefinition UseDirective gql args
options a
_ b
_ = do
  ArgumentsDefinition CONST
directiveDefinitionArgs <- forall a (k' :: TypeCategory). SchemaT OUT a -> SchemaT k' a
outToAny (forall (args :: * -> Constraint).
UseArguments args
-> forall (f :: * -> *) a.
   args a =>
   f a -> SchemaT OUT (ArgumentsDefinition CONST)
useDeriveArguments (forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args -> UseArguments args
dirArgs UseDirective gql args
options) (forall {k} (t :: k). Proxy t
Proxy @a))
  forall (f :: * -> *) a. Applicative f => a -> f a
pure
    ( DirectiveDefinition
        { directiveDefinitionName :: FieldName
directiveDefinitionName = forall (gql :: * -> Constraint) a (f :: * -> *).
gql a =>
UseGQLType gql -> f a -> FieldName
deriveDirectiveName (forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args -> UseGQLType gql
dirGQL UseDirective gql args
options) Proxy a
proxy,
          directiveDefinitionDescription :: Maybe Description
directiveDefinitionDescription = forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> f a -> Maybe Description -> Maybe Description
visitTypeDescription UseDirective gql args
options Proxy a
proxy forall a. Maybe a
Nothing,
          ArgumentsDefinition CONST
directiveDefinitionArgs :: ArgumentsDefinition CONST
directiveDefinitionArgs :: ArgumentsDefinition CONST
directiveDefinitionArgs,
          directiveDefinitionLocations :: [DirectiveLocation]
directiveDefinitionLocations = forall (f :: * -> *) a.
ToLocations (DIRECTIVE_LOCATIONS a) =>
f a -> [DirectiveLocation]
getLocations Proxy a
proxy
        }
    )
  where
    proxy :: Proxy a
proxy = forall {k} (t :: k). Proxy t
Proxy @a

deriveDirectiveUsages :: UseDirective gql args -> [GDirectiveUsage gql args] -> SchemaT kind (Directives CONST)
deriveDirectiveUsages :: forall (gql :: * -> Constraint) (args :: * -> Constraint)
       (kind :: TypeCategory).
UseDirective gql args
-> [GDirectiveUsage gql args] -> SchemaT kind (Directives CONST)
deriveDirectiveUsages UseDirective gql args
options = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall k (m :: * -> *) a. IsMap k m => [(k, a)] -> m a
unsafeFromList forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse (forall (gql :: * -> Constraint) (args :: * -> Constraint)
       (kind :: TypeCategory).
UseDirective gql args
-> GDirectiveUsage gql args
-> SchemaT kind (FieldName, Directive CONST)
toDirectiveTuple UseDirective gql args
options)

toDirectiveTuple ::
  UseDirective gql args ->
  GDirectiveUsage gql args ->
  SchemaT kind (FieldName, Directive CONST)
toDirectiveTuple :: forall (gql :: * -> Constraint) (args :: * -> Constraint)
       (kind :: TypeCategory).
UseDirective gql args
-> GDirectiveUsage gql args
-> SchemaT kind (FieldName, Directive CONST)
toDirectiveTuple UseDirective gql args
options (GDirectiveUsage a
x) = do
  forall (gql :: * -> Constraint) (args :: * -> Constraint) a
       (k :: TypeCategory).
gql a =>
UseDirective gql args
-> (KindedProxy IN a -> SchemaT k (DirectiveDefinition CONST))
-> a
-> SchemaT k ()
insertDirective UseDirective gql args
options (forall a b (kind :: TypeCategory) (gql :: * -> Constraint)
       (args :: * -> Constraint).
(gql a, GQLDirective a, args a) =>
UseDirective gql args
-> a -> b -> SchemaT kind (DirectiveDefinition CONST)
deriveDirectiveDefinition UseDirective gql args
options a
x) a
x
  let directiveName :: FieldName
directiveName = forall (gql :: * -> Constraint) a (f :: * -> *).
gql a =>
UseGQLType gql -> f a -> FieldName
deriveDirectiveName (forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args -> UseGQLType gql
dirGQL UseDirective gql args
options) (forall a. a -> Identity a
Identity a
x)
  [Argument CONST]
args <- forall (t :: * -> *) a. Foldable t => t a -> [a]
toList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (args :: * -> Constraint).
UseArguments args
-> forall (k :: TypeCategory) a.
   args a =>
   a -> SchemaT k (Arguments CONST)
useEncodeArguments (forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args -> UseArguments args
dirArgs UseDirective gql args
options) a
x
  Arguments CONST
directiveArgs <- forall (m :: * -> *) k a (map :: * -> * -> *).
(Monad m, KeyOf k a, FromList m map k a) =>
[a] -> m (map k a)
fromElems (forall a b. (a -> b) -> [a] -> [b]
map Argument CONST -> Argument CONST
editArg [Argument CONST]
args)
  forall (f :: * -> *) a. Applicative f => a -> f a
pure
    ( FieldName
directiveName,
      Directive
        { directivePosition :: Position
directivePosition = Int -> Int -> Position
Position Int
0 Int
0,
          FieldName
directiveName :: FieldName
directiveName :: FieldName
directiveName,
          Arguments CONST
directiveArgs :: Arguments CONST
directiveArgs :: Arguments CONST
directiveArgs
        }
    )
  where
    editArg :: Argument CONST -> Argument CONST
editArg Argument {Value CONST
FieldName
Position
argumentPosition :: forall (valid :: Stage). Argument valid -> Position
argumentName :: forall (valid :: Stage). Argument valid -> FieldName
argumentValue :: forall (valid :: Stage). Argument valid -> Value valid
argumentValue :: Value CONST
argumentName :: FieldName
argumentPosition :: Position
..} = Argument {argumentName :: FieldName
argumentName = forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args -> f a -> FieldName -> FieldName
applyGQLFieldOptions UseDirective gql args
options (forall a. a -> Identity a
Identity a
x) FieldName
argumentName, Value CONST
Position
argumentPosition :: Position
argumentValue :: Value CONST
argumentValue :: Value CONST
argumentPosition :: Position
..}

insertDirective ::
  forall gql args a k.
  gql a =>
  UseDirective gql args ->
  (KindedProxy IN a -> SchemaT k (DirectiveDefinition CONST)) ->
  a ->
  SchemaT k ()
insertDirective :: forall (gql :: * -> Constraint) (args :: * -> Constraint) a
       (k :: TypeCategory).
gql a =>
UseDirective gql args
-> (KindedProxy IN a -> SchemaT k (DirectiveDefinition CONST))
-> a
-> SchemaT k ()
insertDirective UseDirective gql args
ops KindedProxy IN a -> SchemaT k (DirectiveDefinition CONST)
f a
_ = forall a (cat' :: TypeCategory).
TypeFingerprint
-> (a -> SchemaT cat' (DirectiveDefinition CONST))
-> a
-> SchemaT cat' ()
insertDirectiveDefinition (forall (gql :: * -> Constraint).
UseGQLType gql
-> forall (f :: * -> *) a.
   gql a =>
   TypeCategory -> f a -> TypeFingerprint
__useFingerprint (forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args -> UseGQLType gql
dirGQL UseDirective gql args
ops) TypeCategory
IN (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)) KindedProxy IN a -> SchemaT k (DirectiveDefinition CONST)
f KindedProxy IN a
proxy
  where
    proxy :: KindedProxy IN a
proxy = forall {k} {k} (k :: k) (a :: k). KindedProxy k a
KindedProxy :: KindedProxy IN a

getDirHM :: (Ord k, Hashable k, Empty a) => k -> HashMap k a -> a
getDirHM :: forall k a. (Ord k, Hashable k, Empty a) => k -> HashMap k a -> a
getDirHM k
name HashMap k a
xs = forall a. a -> Maybe a -> a
fromMaybe forall coll. Empty coll => coll
empty forall a b. (a -> b) -> a -> b
$ k
name forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
`HM.lookup` HashMap k a
xs

isIncluded :: GDirectiveUsage gql args -> Bool
isIncluded :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> Bool
isIncluded (GDirectiveUsage a
x) = Bool -> Bool
not forall a b. (a -> b) -> a -> b
$ forall a (f :: * -> *). GQLDirective a => f a -> Bool
excludeFromSchema (forall a. a -> Identity a
Identity a
x)

getEnumDirectiveUsages :: gql a => UseDirective gql args -> f a -> TypeName -> [GDirectiveUsage gql args]
getEnumDirectiveUsages :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> f a -> TypeName -> [GDirectiveUsage gql args]
getEnumDirectiveUsages UseDirective {UseArguments args
UseGQLType gql
forall (f :: * -> *) a. gql a => f a -> GDirectiveUsages gql args
__directives :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args
-> forall (f :: * -> *) a.
   gql a =>
   f a -> GDirectiveUsages gql args
dirGQL :: UseGQLType gql
dirArgs :: UseArguments args
__directives :: forall (f :: * -> *) a. gql a => f a -> GDirectiveUsages gql args
dirGQL :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args -> UseGQLType gql
dirArgs :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args -> UseArguments args
..} f a
proxy TypeName
name = forall k a. (Ord k, Hashable k, Empty a) => k -> HashMap k a -> a
getDirHM TypeName
name forall a b. (a -> b) -> a -> b
$ forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args
-> HashMap TypeName [GDirectiveUsage gql args]
enumValueDirectives forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. gql a => f a -> GDirectiveUsages gql args
__directives f a
proxy

getFieldDirectiveUsages :: gql a => UseDirective gql args -> FieldName -> f a -> [GDirectiveUsage gql args]
getFieldDirectiveUsages :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> FieldName -> f a -> [GDirectiveUsage gql args]
getFieldDirectiveUsages UseDirective {UseArguments args
UseGQLType gql
forall (f :: * -> *) a. gql a => f a -> GDirectiveUsages gql args
dirGQL :: UseGQLType gql
dirArgs :: UseArguments args
__directives :: forall (f :: * -> *) a. gql a => f a -> GDirectiveUsages gql args
__directives :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args
-> forall (f :: * -> *) a.
   gql a =>
   f a -> GDirectiveUsages gql args
dirGQL :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args -> UseGQLType gql
dirArgs :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args -> UseArguments args
..} FieldName
name f a
proxy = forall k a. (Ord k, Hashable k, Empty a) => k -> HashMap k a -> a
getDirHM FieldName
name forall a b. (a -> b) -> a -> b
$ forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args
-> HashMap FieldName [GDirectiveUsage gql args]
fieldDirectives forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. gql a => f a -> GDirectiveUsages gql args
__directives f a
proxy

-- derive directives
deriveEnumDirectives :: gql a => UseDirective gql args -> f a -> TypeName -> SchemaT k (Directives CONST)
deriveEnumDirectives :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *) (k :: TypeCategory).
gql a =>
UseDirective gql args
-> f a -> TypeName -> SchemaT k (Directives CONST)
deriveEnumDirectives UseDirective gql args
options f a
proxy TypeName
name = forall (gql :: * -> Constraint) (args :: * -> Constraint)
       (kind :: TypeCategory).
UseDirective gql args
-> [GDirectiveUsage gql args] -> SchemaT kind (Directives CONST)
deriveDirectiveUsages UseDirective gql args
options forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> Bool
isIncluded forall a b. (a -> b) -> a -> b
$ forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> f a -> TypeName -> [GDirectiveUsage gql args]
getEnumDirectiveUsages UseDirective gql args
options f a
proxy TypeName
name

deriveFieldDirectives :: gql a => UseDirective gql args -> f a -> FieldName -> SchemaT kind (Directives CONST)
deriveFieldDirectives :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *) (kind :: TypeCategory).
gql a =>
UseDirective gql args
-> f a -> FieldName -> SchemaT kind (Directives CONST)
deriveFieldDirectives UseDirective gql args
options f a
proxy FieldName
name = forall (gql :: * -> Constraint) (args :: * -> Constraint)
       (kind :: TypeCategory).
UseDirective gql args
-> [GDirectiveUsage gql args] -> SchemaT kind (Directives CONST)
deriveDirectiveUsages UseDirective gql args
options forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> Bool
isIncluded forall a b. (a -> b) -> a -> b
$ forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> FieldName -> f a -> [GDirectiveUsage gql args]
getFieldDirectiveUsages UseDirective gql args
options FieldName
name f a
proxy

deriveTypeDirectives :: gql a => UseDirective gql args -> f a -> SchemaT kind (Directives CONST)
deriveTypeDirectives :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *) (kind :: TypeCategory).
gql a =>
UseDirective gql args -> f a -> SchemaT kind (Directives CONST)
deriveTypeDirectives UseDirective gql args
options f a
proxy = forall (gql :: * -> Constraint) (args :: * -> Constraint)
       (kind :: TypeCategory).
UseDirective gql args
-> [GDirectiveUsage gql args] -> SchemaT kind (Directives CONST)
deriveDirectiveUsages UseDirective gql args
options forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [a]
filter forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> Bool
isIncluded forall a b. (a -> b) -> a -> b
$ forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args -> [GDirectiveUsage gql args]
typeDirectives forall a b. (a -> b) -> a -> b
$ forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args
-> forall (f :: * -> *) a.
   gql a =>
   f a -> GDirectiveUsages gql args
__directives UseDirective gql args
options f a
proxy

-- visit

visitEnumValueDescription :: gql a => UseDirective gql args -> f a -> TypeName -> Maybe Description -> Maybe Description
visitEnumValueDescription :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> f a -> TypeName -> Maybe Description -> Maybe Description
visitEnumValueDescription UseDirective gql args
options f a
proxy TypeName
name Maybe Description
desc = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> Maybe Description -> Maybe Description
applyEnumDescription Maybe Description
desc (forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> f a -> TypeName -> [GDirectiveUsage gql args]
getEnumDirectiveUsages UseDirective gql args
options f a
proxy TypeName
name)

visitEnumName :: gql a => UseDirective gql args -> f a -> TypeName -> TypeName
visitEnumName :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args -> f a -> TypeName -> TypeName
visitEnumName UseDirective gql args
options f a
proxy TypeName
name = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> TypeName -> TypeName
applyEnumName (TypeName -> TypeName
withTypeDirectives TypeName
name) (forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> f a -> TypeName -> [GDirectiveUsage gql args]
getEnumDirectiveUsages UseDirective gql args
options f a
proxy TypeName
name)
  where
    withTypeDirectives :: TypeName -> TypeName
withTypeDirectives TypeName
dirName = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> TypeName -> TypeName
applyTypeEnumNames TypeName
dirName (forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args -> [GDirectiveUsage gql args]
typeDirectives forall a b. (a -> b) -> a -> b
$ forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args
-> forall (f :: * -> *) a.
   gql a =>
   f a -> GDirectiveUsages gql args
__directives UseDirective gql args
options f a
proxy)

visitFieldDescription :: gql a => UseDirective gql args -> f a -> FieldName -> Maybe Description -> Maybe Description
visitFieldDescription :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> f a -> FieldName -> Maybe Description -> Maybe Description
visitFieldDescription UseDirective gql args
options f a
proxy FieldName
name Maybe Description
desc = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> Maybe Description -> Maybe Description
applyFieldDescription Maybe Description
desc (forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> FieldName -> f a -> [GDirectiveUsage gql args]
getFieldDirectiveUsages UseDirective gql args
options FieldName
name f a
proxy)

visitFieldDefaultValue :: gql a => UseDirective gql args -> f a -> FieldName -> Maybe (Value CONST) -> Maybe (Value CONST)
visitFieldDefaultValue :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> f a -> FieldName -> Maybe (Value CONST) -> Maybe (Value CONST)
visitFieldDefaultValue UseDirective gql args
options f a
proxy FieldName
name Maybe (Value CONST)
desc = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args
-> Maybe (Value CONST) -> Maybe (Value CONST)
applyFieldDefaultValue Maybe (Value CONST)
desc (forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> FieldName -> f a -> [GDirectiveUsage gql args]
getFieldDirectiveUsages UseDirective gql args
options FieldName
name f a
proxy)

visitFieldContent ::
  gql a =>
  UseDirective gql args ->
  CatType kind a ->
  FieldName ->
  Maybe (FieldContent TRUE kind CONST) ->
  Maybe (FieldContent TRUE kind CONST)
visitFieldContent :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (kind :: TypeCategory).
gql a =>
UseDirective gql args
-> CatType kind a
-> FieldName
-> Maybe (FieldContent TRUE kind CONST)
-> Maybe (FieldContent TRUE kind CONST)
visitFieldContent UseDirective gql args
options proxy :: CatType kind a
proxy@CatType kind a
InputType FieldName
name Maybe (FieldContent TRUE kind CONST)
x =
  forall (s :: Stage) (cat :: TypeCategory).
Value s -> FieldContent (IN <=? cat) cat s
DefaultInputValue
    forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> f a -> FieldName -> Maybe (Value CONST) -> Maybe (Value CONST)
visitFieldDefaultValue UseDirective gql args
options CatType kind a
proxy FieldName
name (forall (s :: Stage) (cat :: TypeCategory).
FieldContent (IN <=? cat) cat s -> Value s
defaultInputValue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe (FieldContent TRUE kind CONST)
x)
visitFieldContent UseDirective gql args
_ CatType kind a
OutputType FieldName
_ Maybe (FieldContent TRUE kind CONST)
x = Maybe (FieldContent TRUE kind CONST)
x

applyGQLFieldOptions :: gql a => UseDirective gql args -> f a -> FieldName -> FieldName
applyGQLFieldOptions :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args -> f a -> FieldName -> FieldName
applyGQLFieldOptions UseDirective gql args
options f a
proxy = FieldName -> FieldName
withTypeDirectives
  where
    withTypeDirectives :: FieldName -> FieldName
withTypeDirectives FieldName
name = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> FieldName -> FieldName
applyTypeFieldNames FieldName
name (forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args -> [GDirectiveUsage gql args]
typeDirectives forall a b. (a -> b) -> a -> b
$ forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args
-> forall (f :: * -> *) a.
   gql a =>
   f a -> GDirectiveUsages gql args
__directives UseDirective gql args
options f a
proxy)

visitFieldName :: gql a => UseDirective gql args -> f a -> FieldName -> FieldName
visitFieldName :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args -> f a -> FieldName -> FieldName
visitFieldName UseDirective gql args
options f a
proxy FieldName
name = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> FieldName -> FieldName
applyFieldName (forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args -> f a -> FieldName -> FieldName
applyGQLFieldOptions UseDirective gql args
options f a
proxy FieldName
name) (forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> FieldName -> f a -> [GDirectiveUsage gql args]
getFieldDirectiveUsages UseDirective gql args
options FieldName
name f a
proxy)

visitTypeDescription :: gql a => UseDirective gql args -> f a -> Maybe Description -> Maybe Description
visitTypeDescription :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args
-> f a -> Maybe Description -> Maybe Description
visitTypeDescription UseDirective gql args
options f a
proxy Maybe Description
desc = forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> Maybe Description -> Maybe Description
applyTypeDescription Maybe Description
desc (forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args -> [GDirectiveUsage gql args]
typeDirectives forall a b. (a -> b) -> a -> b
$ forall (gql :: * -> Constraint) (args :: * -> Constraint).
UseDirective gql args
-> forall (f :: * -> *) a.
   gql a =>
   f a -> GDirectiveUsages gql args
__directives UseDirective gql args
options f a
proxy)

toFieldRes :: gql a => UseDirective gql args -> f a -> FieldRep v -> (FieldName, v)
toFieldRes :: forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *) v.
gql a =>
UseDirective gql args -> f a -> FieldRep v -> (FieldName, v)
toFieldRes UseDirective gql args
options f a
proxy FieldRep {v
TypeRef
FieldName
fieldValue :: forall a. FieldRep a -> a
fieldTypeRef :: forall a. FieldRep a -> TypeRef
fieldSelector :: forall a. FieldRep a -> FieldName
fieldValue :: v
fieldTypeRef :: TypeRef
fieldSelector :: FieldName
..} = (forall (gql :: * -> Constraint) a (args :: * -> Constraint)
       (f :: * -> *).
gql a =>
UseDirective gql args -> f a -> FieldName -> FieldName
visitFieldName UseDirective gql args
options f a
proxy FieldName
fieldSelector, v
fieldValue)

deriveDirectiveName :: gql a => UseGQLType gql -> f a -> FieldName
deriveDirectiveName :: forall (gql :: * -> Constraint) a (f :: * -> *).
gql a =>
UseGQLType gql -> f a -> FieldName
deriveDirectiveName UseGQLType gql
options f a
proxy = coerce :: forall a b. Coercible a b => a -> b
coerce forall a b. (a -> b) -> a -> b
$ forall (gql :: * -> Constraint).
UseGQLType gql
-> forall (f :: * -> *) a. gql a => TypeCategory -> f a -> TypeName
__useTypename UseGQLType gql
options TypeCategory
IN f a
proxy