{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE NoImplicitPrelude #-}

module Data.Morpheus.Server.Types.DirectiveDefinitions
  ( Prefixes (..),
    Deprecated (..),
  )
where

import Data.Morpheus.Server.Types.Directives (GQLDirective (..))
import Data.Morpheus.Server.Types.GQLType (GQLType (__type))
import Data.Morpheus.Server.Types.Internal
import Data.Morpheus.Server.Types.Visitors (VisitEnum, VisitField, VisitType (..))
import Data.Morpheus.Types.Internal.AST
  ( DirectiveLocation (..),
  )
import qualified Data.Text as T
import Relude

-- | a custom GraphQL directive for adding or removing
-- of prefixes
data Prefixes = Prefixes
  { Prefixes -> Text
addPrefix :: Text,
    Prefixes -> Text
removePrefix :: Text
  }
  deriving (forall x. Rep Prefixes x -> Prefixes
forall x. Prefixes -> Rep Prefixes x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Prefixes x -> Prefixes
$cfrom :: forall x. Prefixes -> Rep Prefixes x
Generic, forall a.
(forall (f :: * -> *). f a -> Maybe Text)
-> (forall (f :: * -> *). f a -> DirectiveUsages)
-> (forall (f :: * -> *). f a -> Map Text Text)
-> (forall (f :: * -> *). f a -> GQLTypeOptions -> GQLTypeOptions)
-> (forall (f :: * -> *). f a -> Map Text (Directives CONST))
-> (forall (f :: * -> *). f a -> Map Text (Value CONST))
-> (forall (f :: * -> *). f a -> Bool)
-> (forall (f :: * -> *). f a -> TypeCategory -> TypeData)
-> GQLType a
forall (f :: * -> *). f Prefixes -> Bool
forall (f :: * -> *). f Prefixes -> Maybe Text
forall (f :: * -> *). f Prefixes -> Map Text Text
forall (f :: * -> *). f Prefixes -> Map Text (Value CONST)
forall (f :: * -> *). f Prefixes -> Map Text (Directives CONST)
forall (f :: * -> *). f Prefixes -> DirectiveUsages
forall (f :: * -> *). f Prefixes -> TypeCategory -> TypeData
forall (f :: * -> *).
f Prefixes -> GQLTypeOptions -> GQLTypeOptions
__type :: forall (f :: * -> *). f Prefixes -> TypeCategory -> TypeData
$c__type :: forall (f :: * -> *). f Prefixes -> TypeCategory -> TypeData
__isEmptyType :: forall (f :: * -> *). f Prefixes -> Bool
$c__isEmptyType :: forall (f :: * -> *). f Prefixes -> Bool
defaultValues :: forall (f :: * -> *). f Prefixes -> Map Text (Value CONST)
$cdefaultValues :: forall (f :: * -> *). f Prefixes -> Map Text (Value CONST)
getDirectives :: forall (f :: * -> *). f Prefixes -> Map Text (Directives CONST)
$cgetDirectives :: forall (f :: * -> *). f Prefixes -> Map Text (Directives CONST)
typeOptions :: forall (f :: * -> *).
f Prefixes -> GQLTypeOptions -> GQLTypeOptions
$ctypeOptions :: forall (f :: * -> *).
f Prefixes -> GQLTypeOptions -> GQLTypeOptions
getDescriptions :: forall (f :: * -> *). f Prefixes -> Map Text Text
$cgetDescriptions :: forall (f :: * -> *). f Prefixes -> Map Text Text
directives :: forall (f :: * -> *). f Prefixes -> DirectiveUsages
$cdirectives :: forall (f :: * -> *). f Prefixes -> DirectiveUsages
description :: forall (f :: * -> *). f Prefixes -> Maybe Text
$cdescription :: forall (f :: * -> *). f Prefixes -> Maybe Text
GQLType)

instance GQLDirective Prefixes where
  type
    DIRECTIVE_LOCATIONS Prefixes =
      '[ 'OBJECT,
         'ENUM,
         'INPUT_OBJECT,
         'UNION,
         'SCALAR,
         'INTERFACE
       ]

instance VisitType Prefixes where
  visitTypeName :: Prefixes -> Text -> Text
visitTypeName Prefixes {Text
addPrefix :: Text
addPrefix :: Prefixes -> Text
addPrefix, Text
removePrefix :: Text
removePrefix :: Prefixes -> Text
removePrefix} Text
name = Text
addPrefix forall a. Semigroup a => a -> a -> a
<> Int -> Text -> Text
T.drop (Text -> Int
T.length Text
removePrefix) Text
name
  visitTypeDescription :: Prefixes -> Maybe Text -> Maybe Text
visitTypeDescription Prefixes
_ = forall a. a -> a
id

-- native GraphQL directive @deprecated
--
newtype Deprecated = Deprecated
  { Deprecated -> Maybe Text
reason :: Maybe Text
  }
  deriving
    ( forall x. Rep Deprecated x -> Deprecated
forall x. Deprecated -> Rep Deprecated x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Deprecated x -> Deprecated
$cfrom :: forall x. Deprecated -> Rep Deprecated x
Generic,
      Deprecated -> Maybe Text -> Maybe Text
Deprecated -> Text -> Text
forall a.
(a -> Text -> Text)
-> (a -> Maybe Text -> Maybe Text) -> VisitEnum a
visitEnumDescription :: Deprecated -> Maybe Text -> Maybe Text
$cvisitEnumDescription :: Deprecated -> Maybe Text -> Maybe Text
visitEnumName :: Deprecated -> Text -> Text
$cvisitEnumName :: Deprecated -> Text -> Text
VisitEnum,
      Deprecated -> Maybe Text -> Maybe Text
Deprecated -> Text -> Text
forall a.
(a -> Text -> Text)
-> (a -> Maybe Text -> Maybe Text) -> VisitField a
visitFieldDescription :: Deprecated -> Maybe Text -> Maybe Text
$cvisitFieldDescription :: Deprecated -> Maybe Text -> Maybe Text
visitFieldName :: Deprecated -> Text -> Text
$cvisitFieldName :: Deprecated -> Text -> Text
VisitField
    )

instance GQLType Deprecated where
  __type :: forall (f :: * -> *). f Deprecated -> TypeCategory -> TypeData
__type f Deprecated
_ = forall a. TypeName -> a -> TypeData
mkTypeData TypeName
"deprecated"

instance GQLDirective Deprecated where
  type
    DIRECTIVE_LOCATIONS Deprecated =
      '[ 'FIELD_DEFINITION,
         'ENUM_VALUE
       ]