{-# LANGUAGE ConstraintKinds #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE GADTs #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE RankNTypes #-} module Data.Morpheus.Server.Deriving.Utils.Use ( UseDirective (..), UseDeriveType (..), UseArguments (..), UseGQLType (..), useTypename, ) where import Data.Morpheus.Server.Deriving.Schema.Internal import Data.Morpheus.Server.Types.Directives ( GDirectiveUsages (..), ) import Data.Morpheus.Server.Types.Internal import Data.Morpheus.Server.Types.SchemaT ( SchemaT, ) import Data.Morpheus.Server.Types.TypeName ( TypeFingerprint, ) import Data.Morpheus.Types.Internal.AST ( Arguments, ArgumentsDefinition, CONST, OUT, TypeCategory (..), TypeName, ) useTypename :: (gqlType a) => UseGQLType gqlType -> CatType c a -> TypeName useTypename :: forall (gqlType :: * -> Constraint) a (c :: TypeCategory). gqlType a => UseGQLType gqlType -> CatType c a -> TypeName useTypename UseGQLType gqlType gql proxy :: CatType c a proxy@CatType c a InputType = forall (gql :: * -> Constraint). UseGQLType gql -> forall (f :: * -> *) a. gql a => TypeCategory -> f a -> TypeName __useTypename UseGQLType gqlType gql TypeCategory IN CatType c a proxy useTypename UseGQLType gqlType gql proxy :: CatType c a proxy@CatType c a OutputType = forall (gql :: * -> Constraint). UseGQLType gql -> forall (f :: * -> *) a. gql a => TypeCategory -> f a -> TypeName __useTypename UseGQLType gqlType gql TypeCategory OUT CatType c a proxy data UseGQLType gql = UseGQLType { forall (gql :: * -> Constraint). UseGQLType gql -> forall (f :: * -> *) a. gql a => TypeCategory -> f a -> TypeFingerprint __useFingerprint :: forall f a. gql a => TypeCategory -> f a -> TypeFingerprint, forall (gql :: * -> Constraint). UseGQLType gql -> forall (f :: * -> *) a. gql a => TypeCategory -> f a -> TypeName __useTypename :: forall f a. gql a => TypeCategory -> f a -> TypeName, forall (gql :: * -> Constraint). UseGQLType gql -> forall (f :: * -> *) a. gql a => f a -> TypeCategory -> TypeData __useTypeData :: forall f a. gql a => f a -> TypeCategory -> TypeData } data UseArguments args = UseArguments { forall (args :: * -> Constraint). UseArguments args -> forall (f :: * -> *) a. args a => f a -> SchemaT 'OUT (ArgumentsDefinition CONST) useDeriveArguments :: forall f a. args a => f a -> SchemaT OUT (ArgumentsDefinition CONST), forall (args :: * -> Constraint). UseArguments args -> forall (k :: TypeCategory) a. args a => a -> SchemaT k (Arguments CONST) useEncodeArguments :: forall k a. args a => a -> SchemaT k (Arguments CONST) } data UseDirective gql args = UseDirective { forall (gql :: * -> Constraint) (args :: * -> Constraint). UseDirective gql args -> forall (f :: * -> *) a. gql a => f a -> GDirectiveUsages gql args __directives :: forall f a. gql a => f a -> GDirectiveUsages gql args, forall (gql :: * -> Constraint) (args :: * -> Constraint). UseDirective gql args -> UseArguments args dirArgs :: UseArguments args, forall (gql :: * -> Constraint) (args :: * -> Constraint). UseDirective gql args -> UseGQLType gql dirGQL :: UseGQLType gql } data UseDeriveType derive = UseDeriveType { forall (derive :: TypeCategory -> * -> Constraint). UseDeriveType derive -> forall (c :: TypeCategory) a. derive c a => CatType c a -> SchemaT c () useDeriveType :: forall c a. derive c a => CatType c a -> SchemaT c (), forall (derive :: TypeCategory -> * -> Constraint). UseDeriveType derive -> forall (c :: TypeCategory) a. derive c a => CatType c a -> TyContentM c useDeriveContent :: forall c a. derive c a => CatType c a -> TyContentM c }