{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
module Data.Morpheus.Server.Types.Directives
( GQLDirective (..),
ToLocations (..),
getLocations,
GDirectiveUsage (..),
GDirectiveUsages (..),
applyTypeName,
applyTypeDescription,
applyEnumName,
applyEnumDescription,
applyFieldName,
applyFieldDescription,
applyFieldDefaultValue,
applyTypeFieldNames,
applyTypeEnumNames,
allUsages,
)
where
import qualified Data.HashMap.Strict as M
import qualified Data.Morpheus.Server.Types.Visitors as Visitors
import Data.Morpheus.Types.Internal.AST
( CONST,
Description,
DirectiveLocation (..),
FALSE,
FieldName,
TRUE,
TypeName,
Value,
packName,
unpackName,
)
import Relude
type family OR (a :: Bool) (b :: Bool) where
OR FALSE FALSE = FALSE
OR a b = TRUE
type family INCLUDES (x :: DirectiveLocation) (xs :: [DirectiveLocation]) :: Bool where
INCLUDES x '[] = FALSE
INCLUDES x (x ': xs) = TRUE
INCLUDES x (a ': xs) = INCLUDES x xs
type family OVERLAPS (xs :: [DirectiveLocation]) (ys :: [DirectiveLocation]) :: Bool where
OVERLAPS (x ': xs) ys = OR (INCLUDES x ys) (OVERLAPS xs ys)
OVERLAPS '[] ys = FALSE
class ToLocation (l :: DirectiveLocation) where
toLocation :: f l -> DirectiveLocation
instance ToLocation 'LOCATION_OBJECT where
toLocation :: forall (f :: DirectiveLocation -> *).
f 'LOCATION_OBJECT -> DirectiveLocation
toLocation = DirectiveLocation -> f 'LOCATION_OBJECT -> DirectiveLocation
forall a b. a -> b -> a
const DirectiveLocation
LOCATION_OBJECT
instance ToLocation 'LOCATION_ENUM where
toLocation :: forall (f :: DirectiveLocation -> *).
f 'LOCATION_ENUM -> DirectiveLocation
toLocation = DirectiveLocation -> f 'LOCATION_ENUM -> DirectiveLocation
forall a b. a -> b -> a
const DirectiveLocation
LOCATION_ENUM
instance ToLocation 'LOCATION_INPUT_OBJECT where
toLocation :: forall (f :: DirectiveLocation -> *).
f 'LOCATION_INPUT_OBJECT -> DirectiveLocation
toLocation = DirectiveLocation -> f 'LOCATION_INPUT_OBJECT -> DirectiveLocation
forall a b. a -> b -> a
const DirectiveLocation
LOCATION_INPUT_OBJECT
instance ToLocation 'LOCATION_UNION where
toLocation :: forall (f :: DirectiveLocation -> *).
f 'LOCATION_UNION -> DirectiveLocation
toLocation = DirectiveLocation -> f 'LOCATION_UNION -> DirectiveLocation
forall a b. a -> b -> a
const DirectiveLocation
LOCATION_UNION
instance ToLocation 'LOCATION_SCALAR where
toLocation :: forall (f :: DirectiveLocation -> *).
f 'LOCATION_SCALAR -> DirectiveLocation
toLocation = DirectiveLocation -> f 'LOCATION_SCALAR -> DirectiveLocation
forall a b. a -> b -> a
const DirectiveLocation
LOCATION_SCALAR
instance ToLocation 'LOCATION_INTERFACE where
toLocation :: forall (f :: DirectiveLocation -> *).
f 'LOCATION_INTERFACE -> DirectiveLocation
toLocation = DirectiveLocation -> f 'LOCATION_INTERFACE -> DirectiveLocation
forall a b. a -> b -> a
const DirectiveLocation
LOCATION_INTERFACE
instance ToLocation 'LOCATION_INPUT_FIELD_DEFINITION where
toLocation :: forall (f :: DirectiveLocation -> *).
f 'LOCATION_INPUT_FIELD_DEFINITION -> DirectiveLocation
toLocation = DirectiveLocation
-> f 'LOCATION_INPUT_FIELD_DEFINITION -> DirectiveLocation
forall a b. a -> b -> a
const DirectiveLocation
LOCATION_INPUT_FIELD_DEFINITION
instance ToLocation 'LOCATION_ARGUMENT_DEFINITION where
toLocation :: forall (f :: DirectiveLocation -> *).
f 'LOCATION_ARGUMENT_DEFINITION -> DirectiveLocation
toLocation = DirectiveLocation
-> f 'LOCATION_ARGUMENT_DEFINITION -> DirectiveLocation
forall a b. a -> b -> a
const DirectiveLocation
LOCATION_ARGUMENT_DEFINITION
instance ToLocation 'LOCATION_FIELD_DEFINITION where
toLocation :: forall (f :: DirectiveLocation -> *).
f 'LOCATION_FIELD_DEFINITION -> DirectiveLocation
toLocation = DirectiveLocation
-> f 'LOCATION_FIELD_DEFINITION -> DirectiveLocation
forall a b. a -> b -> a
const DirectiveLocation
LOCATION_FIELD_DEFINITION
instance ToLocation 'LOCATION_ENUM_VALUE where
toLocation :: forall (f :: DirectiveLocation -> *).
f 'LOCATION_ENUM_VALUE -> DirectiveLocation
toLocation = DirectiveLocation -> f 'LOCATION_ENUM_VALUE -> DirectiveLocation
forall a b. a -> b -> a
const DirectiveLocation
LOCATION_ENUM_VALUE
class ToLocations (k :: [DirectiveLocation]) where
toLocations :: f k -> [DirectiveLocation]
instance (ToLocation l, ToLocations ls) => ToLocations (l : ls) where
toLocations :: forall (f :: [DirectiveLocation] -> *).
f (l : ls) -> [DirectiveLocation]
toLocations f (l : ls)
_ = Proxy l -> DirectiveLocation
forall (l :: DirectiveLocation) (f :: DirectiveLocation -> *).
ToLocation l =>
f l -> DirectiveLocation
forall (f :: DirectiveLocation -> *). f l -> DirectiveLocation
toLocation (forall {k} (t :: k). Proxy t
forall (t :: DirectiveLocation). Proxy t
Proxy @l) DirectiveLocation -> [DirectiveLocation] -> [DirectiveLocation]
forall a. a -> [a] -> [a]
: Proxy ls -> [DirectiveLocation]
forall (k :: [DirectiveLocation]) (f :: [DirectiveLocation] -> *).
ToLocations k =>
f k -> [DirectiveLocation]
forall (f :: [DirectiveLocation] -> *). f ls -> [DirectiveLocation]
toLocations (forall (t :: [DirectiveLocation]). Proxy t
forall {k} (t :: k). Proxy t
Proxy @ls)
instance ToLocations '[] where
toLocations :: forall (f :: [DirectiveLocation] -> *).
f '[] -> [DirectiveLocation]
toLocations f '[]
_ = []
getLocations :: forall f a. ToLocations (DIRECTIVE_LOCATIONS a) => f a -> [DirectiveLocation]
getLocations :: forall (f :: * -> *) a.
ToLocations (DIRECTIVE_LOCATIONS a) =>
f a -> [DirectiveLocation]
getLocations f a
_ = Proxy (DIRECTIVE_LOCATIONS a) -> [DirectiveLocation]
forall (k :: [DirectiveLocation]) (f :: [DirectiveLocation] -> *).
ToLocations k =>
f k -> [DirectiveLocation]
forall (f :: [DirectiveLocation] -> *).
f (DIRECTIVE_LOCATIONS a) -> [DirectiveLocation]
toLocations (Proxy (DIRECTIVE_LOCATIONS a)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (DIRECTIVE_LOCATIONS a))
type ALLOWED (a :: Type) (l :: [DirectiveLocation]) = OVERLAPS l (DIRECTIVE_LOCATIONS a)
type WITH_VISITOR (a :: Type) (f :: Type -> Bool -> Constraint) (l :: [DirectiveLocation]) = f a (ALLOWED a l)
type TYPE_VISITOR_KIND = '[ 'LOCATION_OBJECT, 'LOCATION_ENUM, 'LOCATION_INPUT_OBJECT, 'LOCATION_UNION, 'LOCATION_SCALAR, 'LOCATION_INTERFACE]
type FIELD_VISITOR_KIND = '[ 'LOCATION_INPUT_FIELD_DEFINITION, 'LOCATION_FIELD_DEFINITION]
type ENUM_VISITOR_KIND = '[ 'LOCATION_ENUM_VALUE]
class
( ToLocations (DIRECTIVE_LOCATIONS a),
Typeable a,
WITH_VISITOR a VISIT_TYPE TYPE_VISITOR_KIND,
WITH_VISITOR a VISIT_FIELD FIELD_VISITOR_KIND,
WITH_VISITOR a VISIT_ENUM ENUM_VISITOR_KIND
) =>
GQLDirective a
where
type DIRECTIVE_LOCATIONS a :: [DirectiveLocation]
excludeFromSchema :: f a -> Bool
excludeFromSchema f a
_ = Bool
False
visitTypeName' :: forall a. GQLDirective a => a -> Bool -> TypeName -> TypeName
visitTypeName' :: forall a. GQLDirective a => a -> Bool -> TypeName -> TypeName
visitTypeName' = Proxy
(OR
(INCLUDES 'LOCATION_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_ENUM (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INPUT_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_UNION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_SCALAR (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INTERFACE (DIRECTIVE_LOCATIONS a)) FALSE))))))
-> a -> Bool -> TypeName -> TypeName
forall a (t :: Bool) (f :: Bool -> *).
VISIT_TYPE a t =>
f t -> a -> Bool -> TypeName -> TypeName
forall (f :: Bool -> *).
f (OR
(INCLUDES 'LOCATION_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_ENUM (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INPUT_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_UNION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_SCALAR (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INTERFACE (DIRECTIVE_LOCATIONS a)) FALSE))))))
-> a -> Bool -> TypeName -> TypeName
__visitTypeName (Proxy (ALLOWED a TYPE_VISITOR_KIND)
Proxy
(OR
(INCLUDES 'LOCATION_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_ENUM (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INPUT_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_UNION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_SCALAR (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INTERFACE (DIRECTIVE_LOCATIONS a)) FALSE))))))
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ALLOWED a TYPE_VISITOR_KIND))
visitTypeDescription' :: forall a. GQLDirective a => a -> Maybe Description -> Maybe Description
visitTypeDescription' :: forall a.
GQLDirective a =>
a -> Maybe Description -> Maybe Description
visitTypeDescription' = Proxy
(OR
(INCLUDES 'LOCATION_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_ENUM (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INPUT_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_UNION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_SCALAR (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INTERFACE (DIRECTIVE_LOCATIONS a)) FALSE))))))
-> a -> Maybe Description -> Maybe Description
forall a (t :: Bool) (f :: Bool -> *).
VISIT_TYPE a t =>
f t -> a -> Maybe Description -> Maybe Description
forall (f :: Bool -> *).
f (OR
(INCLUDES 'LOCATION_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_ENUM (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INPUT_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_UNION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_SCALAR (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INTERFACE (DIRECTIVE_LOCATIONS a)) FALSE))))))
-> a -> Maybe Description -> Maybe Description
__visitTypeDescription (Proxy (ALLOWED a TYPE_VISITOR_KIND)
Proxy
(OR
(INCLUDES 'LOCATION_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_ENUM (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INPUT_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_UNION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_SCALAR (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INTERFACE (DIRECTIVE_LOCATIONS a)) FALSE))))))
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ALLOWED a TYPE_VISITOR_KIND))
visitFieldNames' :: forall a. GQLDirective a => a -> FieldName -> FieldName
visitFieldNames' :: forall a. GQLDirective a => a -> FieldName -> FieldName
visitFieldNames' = Proxy
(OR
(INCLUDES 'LOCATION_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_ENUM (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INPUT_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_UNION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_SCALAR (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INTERFACE (DIRECTIVE_LOCATIONS a)) FALSE))))))
-> a -> FieldName -> FieldName
forall a (t :: Bool) (f :: Bool -> *).
VISIT_TYPE a t =>
f t -> a -> FieldName -> FieldName
forall (f :: Bool -> *).
f (OR
(INCLUDES 'LOCATION_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_ENUM (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INPUT_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_UNION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_SCALAR (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INTERFACE (DIRECTIVE_LOCATIONS a)) FALSE))))))
-> a -> FieldName -> FieldName
__visitFieldNames (Proxy (ALLOWED a TYPE_VISITOR_KIND)
Proxy
(OR
(INCLUDES 'LOCATION_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_ENUM (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INPUT_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_UNION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_SCALAR (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INTERFACE (DIRECTIVE_LOCATIONS a)) FALSE))))))
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ALLOWED a TYPE_VISITOR_KIND))
visitEnumNames' :: forall a. GQLDirective a => a -> TypeName -> TypeName
visitEnumNames' :: forall a. GQLDirective a => a -> TypeName -> TypeName
visitEnumNames' = Proxy
(OR
(INCLUDES 'LOCATION_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_ENUM (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INPUT_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_UNION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_SCALAR (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INTERFACE (DIRECTIVE_LOCATIONS a)) FALSE))))))
-> a -> TypeName -> TypeName
forall a (t :: Bool) (f :: Bool -> *).
VISIT_TYPE a t =>
f t -> a -> TypeName -> TypeName
forall (f :: Bool -> *).
f (OR
(INCLUDES 'LOCATION_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_ENUM (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INPUT_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_UNION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_SCALAR (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INTERFACE (DIRECTIVE_LOCATIONS a)) FALSE))))))
-> a -> TypeName -> TypeName
__visitEnumNames (Proxy (ALLOWED a TYPE_VISITOR_KIND)
Proxy
(OR
(INCLUDES 'LOCATION_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_ENUM (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INPUT_OBJECT (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_UNION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_SCALAR (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_INTERFACE (DIRECTIVE_LOCATIONS a)) FALSE))))))
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ALLOWED a TYPE_VISITOR_KIND))
class VISIT_TYPE a (t :: Bool) where
__visitTypeName :: f t -> a -> Bool -> TypeName -> TypeName
__visitTypeDescription :: f t -> a -> Maybe Description -> Maybe Description
__visitFieldNames :: f t -> a -> FieldName -> FieldName
__visitEnumNames :: f t -> a -> TypeName -> TypeName
instance VISIT_TYPE a 'False where
__visitTypeName :: forall (f :: Bool -> *).
f FALSE -> a -> Bool -> TypeName -> TypeName
__visitTypeName f FALSE
_ a
_ Bool
_ = TypeName -> TypeName
forall a. a -> a
id
__visitTypeDescription :: forall (f :: Bool -> *).
f FALSE -> a -> Maybe Description -> Maybe Description
__visitTypeDescription f FALSE
_ a
_ = Maybe Description -> Maybe Description
forall a. a -> a
id
__visitFieldNames :: forall (f :: Bool -> *). f FALSE -> a -> FieldName -> FieldName
__visitFieldNames f FALSE
_ a
_ = FieldName -> FieldName
forall a. a -> a
id
__visitEnumNames :: forall (f :: Bool -> *). f FALSE -> a -> TypeName -> TypeName
__visitEnumNames f FALSE
_ a
_ = TypeName -> TypeName
forall a. a -> a
id
instance Visitors.VisitType a => VISIT_TYPE a TRUE where
__visitTypeName :: forall (f :: Bool -> *).
f TRUE -> a -> Bool -> TypeName -> TypeName
__visitTypeName f TRUE
_ a
x Bool
isInput TypeName
name = Description -> TypeName
forall a (t :: NAME). NamePacking a => a -> Name t
forall (t :: NAME). Description -> Name t
packName (Description -> TypeName) -> Description -> TypeName
forall a b. (a -> b) -> a -> b
$ a -> Bool -> Description -> Description
forall a. VisitType a => a -> Bool -> Description -> Description
Visitors.visitTypeName a
x Bool
isInput (TypeName -> Description
forall a (t :: NAME). NamePacking a => Name t -> a
forall (t :: NAME). Name t -> Description
unpackName TypeName
name)
__visitTypeDescription :: forall (f :: Bool -> *).
f TRUE -> a -> Maybe Description -> Maybe Description
__visitTypeDescription f TRUE
_ = a -> Maybe Description -> Maybe Description
forall a.
VisitType a =>
a -> Maybe Description -> Maybe Description
Visitors.visitTypeDescription
__visitFieldNames :: forall (f :: Bool -> *). f TRUE -> a -> FieldName -> FieldName
__visitFieldNames f TRUE
_ a
x = Description -> FieldName
forall a (t :: NAME). NamePacking a => a -> Name t
forall (t :: NAME). Description -> Name t
packName (Description -> FieldName)
-> (FieldName -> Description) -> FieldName -> FieldName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Description -> Description
forall a. VisitType a => a -> Description -> Description
Visitors.visitFieldNames a
x (Description -> Description)
-> (FieldName -> Description) -> FieldName -> Description
forall b c a. (b -> c) -> (a -> b) -> a -> c
. FieldName -> Description
forall a (t :: NAME). NamePacking a => Name t -> a
forall (t :: NAME). Name t -> Description
unpackName
__visitEnumNames :: forall (f :: Bool -> *). f TRUE -> a -> TypeName -> TypeName
__visitEnumNames f TRUE
_ a
x = Description -> TypeName
forall a (t :: NAME). NamePacking a => a -> Name t
forall (t :: NAME). Description -> Name t
packName (Description -> TypeName)
-> (TypeName -> Description) -> TypeName -> TypeName
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Description -> Description
forall a. VisitType a => a -> Description -> Description
Visitors.visitEnumNames a
x (Description -> Description)
-> (TypeName -> Description) -> TypeName -> Description
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeName -> Description
forall a (t :: NAME). NamePacking a => Name t -> a
forall (t :: NAME). Name t -> Description
unpackName
visitFieldName' :: forall a. GQLDirective a => a -> FieldName -> FieldName
visitFieldName' :: forall a. GQLDirective a => a -> FieldName -> FieldName
visitFieldName' = Proxy
(OR
(INCLUDES 'LOCATION_INPUT_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
FALSE))
-> a -> FieldName -> FieldName
forall a (t :: Bool) (f :: Bool -> *).
VISIT_FIELD a t =>
f t -> a -> FieldName -> FieldName
forall (f :: Bool -> *).
f (OR
(INCLUDES 'LOCATION_INPUT_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
FALSE))
-> a -> FieldName -> FieldName
__visitFieldName (Proxy (ALLOWED a FIELD_VISITOR_KIND)
Proxy
(OR
(INCLUDES 'LOCATION_INPUT_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
FALSE))
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ALLOWED a FIELD_VISITOR_KIND))
visitFieldDescription' :: forall a. GQLDirective a => a -> Maybe Description -> Maybe Description
visitFieldDescription' :: forall a.
GQLDirective a =>
a -> Maybe Description -> Maybe Description
visitFieldDescription' = Proxy
(OR
(INCLUDES 'LOCATION_INPUT_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
FALSE))
-> a -> Maybe Description -> Maybe Description
forall a (t :: Bool) (f :: Bool -> *).
VISIT_FIELD a t =>
f t -> a -> Maybe Description -> Maybe Description
forall (f :: Bool -> *).
f (OR
(INCLUDES 'LOCATION_INPUT_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
FALSE))
-> a -> Maybe Description -> Maybe Description
__visitFieldDescription (Proxy (ALLOWED a FIELD_VISITOR_KIND)
Proxy
(OR
(INCLUDES 'LOCATION_INPUT_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
FALSE))
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ALLOWED a FIELD_VISITOR_KIND))
visitFieldDefaultValue' :: forall a. GQLDirective a => a -> Maybe (Value CONST) -> Maybe (Value CONST)
visitFieldDefaultValue' :: forall a.
GQLDirective a =>
a -> Maybe (Value CONST) -> Maybe (Value CONST)
visitFieldDefaultValue' = Proxy
(OR
(INCLUDES 'LOCATION_INPUT_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
FALSE))
-> a -> Maybe (Value CONST) -> Maybe (Value CONST)
forall a (t :: Bool) (f :: Bool -> *).
VISIT_FIELD a t =>
f t -> a -> Maybe (Value CONST) -> Maybe (Value CONST)
forall (f :: Bool -> *).
f (OR
(INCLUDES 'LOCATION_INPUT_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
FALSE))
-> a -> Maybe (Value CONST) -> Maybe (Value CONST)
__visitFieldDefaultValue (Proxy (ALLOWED a FIELD_VISITOR_KIND)
Proxy
(OR
(INCLUDES 'LOCATION_INPUT_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
(OR
(INCLUDES 'LOCATION_FIELD_DEFINITION (DIRECTIVE_LOCATIONS a))
FALSE))
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ALLOWED a FIELD_VISITOR_KIND))
class VISIT_FIELD a (t :: Bool) where
__visitFieldName :: f t -> a -> FieldName -> FieldName
__visitFieldDescription :: f t -> a -> Maybe Description -> Maybe Description
__visitFieldDefaultValue :: f t -> a -> Maybe (Value CONST) -> Maybe (Value CONST)
instance VISIT_FIELD a FALSE where
__visitFieldName :: forall (f :: Bool -> *). f FALSE -> a -> FieldName -> FieldName
__visitFieldName f FALSE
_ a
_ = FieldName -> FieldName
forall a. a -> a
id
__visitFieldDescription :: forall (f :: Bool -> *).
f FALSE -> a -> Maybe Description -> Maybe Description
__visitFieldDescription f FALSE
_ a
_ = Maybe Description -> Maybe Description
forall a. a -> a
id
__visitFieldDefaultValue :: forall (f :: Bool -> *).
f FALSE -> a -> Maybe (Value CONST) -> Maybe (Value CONST)
__visitFieldDefaultValue f FALSE
_ a
_ = Maybe (Value CONST) -> Maybe (Value CONST)
forall a. a -> a
id
instance Visitors.VisitField a => VISIT_FIELD a TRUE where
__visitFieldName :: forall (f :: Bool -> *). f TRUE -> a -> FieldName -> FieldName
__visitFieldName f TRUE
_ a
x FieldName
name = Description -> FieldName
forall a (t :: NAME). NamePacking a => a -> Name t
forall (t :: NAME). Description -> Name t
packName (Description -> FieldName) -> Description -> FieldName
forall a b. (a -> b) -> a -> b
$ a -> Description -> Description
forall a. VisitField a => a -> Description -> Description
Visitors.visitFieldName a
x (FieldName -> Description
forall a (t :: NAME). NamePacking a => Name t -> a
forall (t :: NAME). Name t -> Description
unpackName FieldName
name)
__visitFieldDescription :: forall (f :: Bool -> *).
f TRUE -> a -> Maybe Description -> Maybe Description
__visitFieldDescription f TRUE
_ = a -> Maybe Description -> Maybe Description
forall a.
VisitField a =>
a -> Maybe Description -> Maybe Description
Visitors.visitFieldDescription
__visitFieldDefaultValue :: forall (f :: Bool -> *).
f TRUE -> a -> Maybe (Value CONST) -> Maybe (Value CONST)
__visitFieldDefaultValue f TRUE
_ = a -> Maybe (Value CONST) -> Maybe (Value CONST)
forall a.
VisitField a =>
a -> Maybe (Value CONST) -> Maybe (Value CONST)
Visitors.visitFieldDefaultValue
visitEnumName' :: forall a. GQLDirective a => a -> TypeName -> TypeName
visitEnumName' :: forall a. GQLDirective a => a -> TypeName -> TypeName
visitEnumName' = Proxy
(OR (INCLUDES 'LOCATION_ENUM_VALUE (DIRECTIVE_LOCATIONS a)) FALSE)
-> a -> TypeName -> TypeName
forall a (t :: Bool) (f :: Bool -> *).
VISIT_ENUM a t =>
f t -> a -> TypeName -> TypeName
forall (f :: Bool -> *).
f (OR
(INCLUDES 'LOCATION_ENUM_VALUE (DIRECTIVE_LOCATIONS a)) FALSE)
-> a -> TypeName -> TypeName
__visitEnumName (Proxy (ALLOWED a ENUM_VISITOR_KIND)
Proxy
(OR (INCLUDES 'LOCATION_ENUM_VALUE (DIRECTIVE_LOCATIONS a)) FALSE)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ALLOWED a ENUM_VISITOR_KIND))
visitEnumDescription' :: forall a. GQLDirective a => a -> Maybe Description -> Maybe Description
visitEnumDescription' :: forall a.
GQLDirective a =>
a -> Maybe Description -> Maybe Description
visitEnumDescription' = Proxy
(OR (INCLUDES 'LOCATION_ENUM_VALUE (DIRECTIVE_LOCATIONS a)) FALSE)
-> a -> Maybe Description -> Maybe Description
forall a (t :: Bool) (f :: Bool -> *).
VISIT_ENUM a t =>
f t -> a -> Maybe Description -> Maybe Description
forall (f :: Bool -> *).
f (OR
(INCLUDES 'LOCATION_ENUM_VALUE (DIRECTIVE_LOCATIONS a)) FALSE)
-> a -> Maybe Description -> Maybe Description
__visitEnumDescription (Proxy (ALLOWED a ENUM_VISITOR_KIND)
Proxy
(OR (INCLUDES 'LOCATION_ENUM_VALUE (DIRECTIVE_LOCATIONS a)) FALSE)
forall {k} (t :: k). Proxy t
Proxy :: Proxy (ALLOWED a ENUM_VISITOR_KIND))
class VISIT_ENUM a (t :: Bool) where
__visitEnumName :: f t -> a -> TypeName -> TypeName
__visitEnumDescription :: f t -> a -> Maybe Description -> Maybe Description
instance VISIT_ENUM a FALSE where
__visitEnumName :: forall (f :: Bool -> *). f FALSE -> a -> TypeName -> TypeName
__visitEnumName f FALSE
_ a
_ = TypeName -> TypeName
forall a. a -> a
id
__visitEnumDescription :: forall (f :: Bool -> *).
f FALSE -> a -> Maybe Description -> Maybe Description
__visitEnumDescription f FALSE
_ a
_ = Maybe Description -> Maybe Description
forall a. a -> a
id
instance Visitors.VisitEnum a => VISIT_ENUM a TRUE where
__visitEnumName :: forall (f :: Bool -> *). f TRUE -> a -> TypeName -> TypeName
__visitEnumName f TRUE
_ a
x TypeName
name = Description -> TypeName
forall a (t :: NAME). NamePacking a => a -> Name t
forall (t :: NAME). Description -> Name t
packName (Description -> TypeName) -> Description -> TypeName
forall a b. (a -> b) -> a -> b
$ a -> Description -> Description
forall a. VisitEnum a => a -> Description -> Description
Visitors.visitEnumName a
x (TypeName -> Description
forall a (t :: NAME). NamePacking a => Name t -> a
forall (t :: NAME). Name t -> Description
unpackName TypeName
name)
__visitEnumDescription :: forall (f :: Bool -> *).
f TRUE -> a -> Maybe Description -> Maybe Description
__visitEnumDescription f TRUE
_ = a -> Maybe Description -> Maybe Description
forall a.
VisitEnum a =>
a -> Maybe Description -> Maybe Description
Visitors.visitEnumDescription
data GDirectiveUsage (gql :: Type -> Constraint) (args :: Type -> Constraint) where
GDirectiveUsage :: (GQLDirective a, gql a, args a) => a -> GDirectiveUsage gql args
applyTypeName :: GDirectiveUsage gql args -> Bool -> TypeName -> TypeName
applyTypeName :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> Bool -> TypeName -> TypeName
applyTypeName (GDirectiveUsage a
x) = a -> Bool -> TypeName -> TypeName
forall a. GQLDirective a => a -> Bool -> TypeName -> TypeName
visitTypeName' a
x
applyTypeFieldNames :: GDirectiveUsage gql args -> FieldName -> FieldName
applyTypeFieldNames :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> FieldName -> FieldName
applyTypeFieldNames (GDirectiveUsage a
x) = a -> FieldName -> FieldName
forall a. GQLDirective a => a -> FieldName -> FieldName
visitFieldNames' a
x
applyTypeEnumNames :: GDirectiveUsage gql args -> TypeName -> TypeName
applyTypeEnumNames :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> TypeName -> TypeName
applyTypeEnumNames (GDirectiveUsage a
x) = a -> TypeName -> TypeName
forall a. GQLDirective a => a -> TypeName -> TypeName
visitEnumNames' a
x
applyEnumDescription :: GDirectiveUsage gql args -> Maybe Description -> Maybe Description
applyEnumDescription :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> Maybe Description -> Maybe Description
applyEnumDescription (GDirectiveUsage a
x) = a -> Maybe Description -> Maybe Description
forall a.
GQLDirective a =>
a -> Maybe Description -> Maybe Description
visitEnumDescription' a
x
applyEnumName :: GDirectiveUsage gql args -> TypeName -> TypeName
applyEnumName :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> TypeName -> TypeName
applyEnumName (GDirectiveUsage a
x) = a -> TypeName -> TypeName
forall a. GQLDirective a => a -> TypeName -> TypeName
visitEnumName' a
x
applyFieldName :: GDirectiveUsage gql args -> FieldName -> FieldName
applyFieldName :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> FieldName -> FieldName
applyFieldName (GDirectiveUsage a
x) = a -> FieldName -> FieldName
forall a. GQLDirective a => a -> FieldName -> FieldName
visitFieldName' a
x
applyFieldDescription :: GDirectiveUsage gql args -> Maybe Description -> Maybe Description
applyFieldDescription :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> Maybe Description -> Maybe Description
applyFieldDescription (GDirectiveUsage a
x) = a -> Maybe Description -> Maybe Description
forall a.
GQLDirective a =>
a -> Maybe Description -> Maybe Description
visitFieldDescription' a
x
applyFieldDefaultValue :: GDirectiveUsage gql args -> Maybe (Value CONST) -> Maybe (Value CONST)
applyFieldDefaultValue :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args
-> Maybe (Value CONST) -> Maybe (Value CONST)
applyFieldDefaultValue (GDirectiveUsage a
x) = a -> Maybe (Value CONST) -> Maybe (Value CONST)
forall a.
GQLDirective a =>
a -> Maybe (Value CONST) -> Maybe (Value CONST)
visitFieldDefaultValue' a
x
applyTypeDescription :: GDirectiveUsage gql args -> Maybe Description -> Maybe Description
applyTypeDescription :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsage gql args -> Maybe Description -> Maybe Description
applyTypeDescription (GDirectiveUsage a
x) = a -> Maybe Description -> Maybe Description
forall a.
GQLDirective a =>
a -> Maybe Description -> Maybe Description
visitTypeDescription' a
x
data GDirectiveUsages gql args = GDirectiveUsages
{ forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args -> [GDirectiveUsage gql args]
typeDirectives :: [GDirectiveUsage gql args],
forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args
-> HashMap FieldName [GDirectiveUsage gql args]
fieldDirectives :: M.HashMap FieldName [GDirectiveUsage gql args],
forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args
-> HashMap TypeName [GDirectiveUsage gql args]
enumValueDirectives :: M.HashMap TypeName [GDirectiveUsage gql args]
}
allUsages :: GDirectiveUsages gql args -> [GDirectiveUsage gql args]
allUsages :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args -> [GDirectiveUsage gql args]
allUsages GDirectiveUsages {[GDirectiveUsage gql args]
HashMap TypeName [GDirectiveUsage gql args]
HashMap FieldName [GDirectiveUsage gql args]
typeDirectives :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args -> [GDirectiveUsage gql args]
fieldDirectives :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args
-> HashMap FieldName [GDirectiveUsage gql args]
enumValueDirectives :: forall (gql :: * -> Constraint) (args :: * -> Constraint).
GDirectiveUsages gql args
-> HashMap TypeName [GDirectiveUsage gql args]
typeDirectives :: [GDirectiveUsage gql args]
fieldDirectives :: HashMap FieldName [GDirectiveUsage gql args]
enumValueDirectives :: HashMap TypeName [GDirectiveUsage gql args]
..} =
[[GDirectiveUsage gql args]] -> [GDirectiveUsage gql args]
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (HashMap TypeName [GDirectiveUsage gql args]
-> [[GDirectiveUsage gql args]]
forall a. HashMap TypeName a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList HashMap TypeName [GDirectiveUsage gql args]
enumValueDirectives)
[GDirectiveUsage gql args]
-> [GDirectiveUsage gql args] -> [GDirectiveUsage gql args]
forall a. Semigroup a => a -> a -> a
<> [[GDirectiveUsage gql args]] -> [GDirectiveUsage gql args]
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (HashMap FieldName [GDirectiveUsage gql args]
-> [[GDirectiveUsage gql args]]
forall a. HashMap FieldName a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
toList HashMap FieldName [GDirectiveUsage gql args]
fieldDirectives)
[GDirectiveUsage gql args]
-> [GDirectiveUsage gql args] -> [GDirectiveUsage gql args]
forall a. Semigroup a => a -> a -> a
<> [GDirectiveUsage gql args]
typeDirectives
instance Monoid (GDirectiveUsages gql args) where
mempty :: GDirectiveUsages gql args
mempty = [GDirectiveUsage gql args]
-> HashMap FieldName [GDirectiveUsage gql args]
-> HashMap TypeName [GDirectiveUsage gql args]
-> GDirectiveUsages gql args
forall (gql :: * -> Constraint) (args :: * -> Constraint).
[GDirectiveUsage gql args]
-> HashMap FieldName [GDirectiveUsage gql args]
-> HashMap TypeName [GDirectiveUsage gql args]
-> GDirectiveUsages gql args
GDirectiveUsages [GDirectiveUsage gql args]
forall a. Monoid a => a
mempty HashMap FieldName [GDirectiveUsage gql args]
forall a. Monoid a => a
mempty HashMap TypeName [GDirectiveUsage gql args]
forall a. Monoid a => a
mempty
instance Semigroup (GDirectiveUsages gql args) where
GDirectiveUsages [GDirectiveUsage gql args]
td1 HashMap FieldName [GDirectiveUsage gql args]
fd1 HashMap TypeName [GDirectiveUsage gql args]
ed1 <> :: GDirectiveUsages gql args
-> GDirectiveUsages gql args -> GDirectiveUsages gql args
<> GDirectiveUsages [GDirectiveUsage gql args]
td2 HashMap FieldName [GDirectiveUsage gql args]
fd2 HashMap TypeName [GDirectiveUsage gql args]
ed2 =
[GDirectiveUsage gql args]
-> HashMap FieldName [GDirectiveUsage gql args]
-> HashMap TypeName [GDirectiveUsage gql args]
-> GDirectiveUsages gql args
forall (gql :: * -> Constraint) (args :: * -> Constraint).
[GDirectiveUsage gql args]
-> HashMap FieldName [GDirectiveUsage gql args]
-> HashMap TypeName [GDirectiveUsage gql args]
-> GDirectiveUsages gql args
GDirectiveUsages ([GDirectiveUsage gql args]
td1 [GDirectiveUsage gql args]
-> [GDirectiveUsage gql args] -> [GDirectiveUsage gql args]
forall a. Semigroup a => a -> a -> a
<> [GDirectiveUsage gql args]
td2) (HashMap FieldName [GDirectiveUsage gql args]
-> HashMap FieldName [GDirectiveUsage gql args]
-> HashMap FieldName [GDirectiveUsage gql args]
forall k v.
(Eq k, Hashable k, Semigroup v) =>
HashMap k v -> HashMap k v -> HashMap k v
mergeDirs HashMap FieldName [GDirectiveUsage gql args]
fd1 HashMap FieldName [GDirectiveUsage gql args]
fd2) (HashMap TypeName [GDirectiveUsage gql args]
-> HashMap TypeName [GDirectiveUsage gql args]
-> HashMap TypeName [GDirectiveUsage gql args]
forall k v.
(Eq k, Hashable k, Semigroup v) =>
HashMap k v -> HashMap k v -> HashMap k v
mergeDirs HashMap TypeName [GDirectiveUsage gql args]
ed1 HashMap TypeName [GDirectiveUsage gql args]
ed2)
mergeDirs :: (Eq k, Hashable k, Semigroup v) => HashMap k v -> HashMap k v -> HashMap k v
mergeDirs :: forall k v.
(Eq k, Hashable k, Semigroup v) =>
HashMap k v -> HashMap k v -> HashMap k v
mergeDirs HashMap k v
a HashMap k v
b = HashMap k v -> [(k, v)] -> HashMap k v
forall {k} {v}.
(Hashable k, Semigroup v) =>
HashMap k v -> [(k, v)] -> HashMap k v
update HashMap k v
a (HashMap k v -> [(k, v)]
forall k v. HashMap k v -> [(k, v)]
M.toList HashMap k v
b)
where
update :: HashMap k v -> [(k, v)] -> HashMap k v
update HashMap k v
m [] = HashMap k v
m
update HashMap k v
m ((k, v)
x : [(k, v)]
xs) = HashMap k v -> [(k, v)] -> HashMap k v
update ((k, v) -> HashMap k v -> HashMap k v
forall k v.
(Eq k, Hashable k, Semigroup v) =>
(k, v) -> HashMap k v -> HashMap k v
upsert (k, v)
x HashMap k v
m) [(k, v)]
xs
upsert :: (Eq k, Hashable k, Semigroup v) => (k, v) -> HashMap k v -> HashMap k v
upsert :: forall k v.
(Eq k, Hashable k, Semigroup v) =>
(k, v) -> HashMap k v -> HashMap k v
upsert (k
k, v
v) = (Maybe v -> Maybe v) -> k -> HashMap k v -> HashMap k v
forall k v.
(Eq k, Hashable k) =>
(Maybe v -> Maybe v) -> k -> HashMap k v -> HashMap k v
M.alter (v -> Maybe v
forall a. a -> Maybe a
Just (v -> Maybe v) -> (Maybe v -> v) -> Maybe v -> Maybe v
forall b c a. (b -> c) -> (a -> b) -> a -> c
. v -> (v -> v) -> Maybe v -> v
forall b a. b -> (a -> b) -> Maybe a -> b
maybe v
v (v
v v -> v -> v
forall a. Semigroup a => a -> a -> a
<>)) k
k