Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
GQL Types
Synopsis
- class GQLType a where
- type KIND a :: DerivingKind
- description :: f a -> Maybe Text
- directives :: f a -> DirectiveUsages
- getDescriptions :: f a -> Map Text Description
- typeOptions :: f a -> GQLTypeOptions -> GQLTypeOptions
- getDirectives :: f a -> Map Text (Directives CONST)
- defaultValues :: f a -> Map Text (Value CONST)
- class EncodeScalar a where
- encodeScalar :: a -> ScalarValue
- class EncodeWrapper (wrapper :: Type -> Type) where
- encodeWrapper :: Monad m => (a -> m (ResolverValue m)) -> wrapper a -> m (ResolverValue m)
- class DecodeScalar a where
- decodeScalar :: ScalarValue -> Either Text a
- class DecodeWrapper (f :: Type -> Type) where
- decodeWrapper :: (Monad m, DecodeWrapperConstraint f a) => (ValidValue -> m a) -> ValidValue -> ExceptT GQLError m (f a)
- data GQLRequest = GQLRequest {}
- data GQLResponse
- = Data ValidValue
- | Errors [GQLError]
- newtype ID = ID {}
- data ScalarValue
- data RootResolver (m :: Type -> Type) event (query :: (Type -> Type) -> Type) (mutation :: (Type -> Type) -> Type) (subscription :: (Type -> Type) -> Type) = RootResolver {
- queryResolver :: query (Resolver QUERY event m)
- mutationResolver :: mutation (Resolver MUTATION event m)
- subscriptionResolver :: subscription (Resolver SUBSCRIPTION event m)
- constRes :: forall (o :: OperationType) (m :: Type -> Type) b a e. (WithOperation o, Monad m) => b -> a -> Resolver o e m b
- constMutRes :: Monad m => [e] -> a -> args -> ResolverM e m a
- data Undefined (m :: Type -> Type)
- data Resolver (o :: OperationType) event (m :: Type -> Type) value
- type QUERY = 'Query
- type MUTATION = 'Mutation
- type SUBSCRIPTION = 'Subscription
- lift :: (MonadTrans t, Monad m) => m a -> t m a
- liftEither :: (MonadTrans t, Monad (t m), MonadError GQLError (t m)) => Monad m => m (Either String a) -> t m a
- failRes :: (Monad m, WithOperation o) => String -> Resolver o e m a
- type WithOperation (o :: OperationType) = LiftOperation o
- publish :: forall (m :: Type -> Type) e. Monad m => [e] -> Resolver MUTATION e m ()
- subscribe :: forall (m :: Type -> Type) e a. Monad m => Channel e -> Resolver QUERY e m (e -> Resolver SUBSCRIPTION e m a) -> SubscriptionField (Resolver SUBSCRIPTION e m a)
- unsafeInternalContext :: forall (m :: Type -> Type) (o :: OperationType) e. (Monad m, LiftOperation o) => Resolver o e m ResolverContext
- data ResolverContext = ResolverContext {}
- type ResolverO (o :: OperationType) e (m :: Type -> Type) (a :: k) = Flexible (Resolver o e m) a
- type ComposedResolver (o :: OperationType) e (m :: Type -> Type) (f :: Type -> Type) (a :: k) = Composed (Resolver o e m) f a
- type ResolverQ e (m :: Type -> Type) (a :: k) = Flexible (Resolver QUERY e m) a
- type ResolverM e (m :: Type -> Type) (a :: k) = Flexible (Resolver MUTATION e m) a
- type ResolverS e (m :: Type -> Type) (a :: k) = Flexible (Resolver SUBSCRIPTION e m) a
- type ResolveQ e m a = ResolverQ e m a
- type ResolveM e m a = ResolverM e m a
- type ResolveS e m a = ResolverS e m a
- type Res = Resolver QUERY
- type MutRes = Resolver MUTATION
- type SubRes = Resolver SUBSCRIPTION
- type IORes e = Res e IO
- type IOMutRes e = MutRes e IO
- type IOSubRes e = SubRes e IO
- data SubscriptionField a
- data App event (m :: Type -> Type)
- class RenderGQL a
- render :: RenderGQL a => a -> ByteString
- data TypeGuard interface union
- = ResolveInterface interface
- | ResolveType union
- newtype Arg (name :: Symbol) a = Arg {
- argValue :: a
- data NamedResolvers (m :: Type -> Type) event (qu :: (Type -> Type) -> Type) (mu :: (Type -> Type) -> Type) (su :: (Type -> Type) -> Type) = ResolveNamed (Resolver QUERY event m) (qu (NamedResolverT (Resolver QUERY event m))) => NamedResolvers
- data GQLTypeOptions
- defaultTypeOptions :: GQLTypeOptions
- fieldLabelModifier :: GQLTypeOptions -> String -> String
- constructorTagModifier :: GQLTypeOptions -> String -> String
- typeNameModifier :: GQLTypeOptions -> Bool -> String -> String
- defaultRootResolver :: forall (m :: Type -> Type) event. RootResolver m event Undefined Undefined Undefined
- data Prefixes = Prefixes {
- addPrefix :: Text
- removePrefix :: Text
- class VisitType a where
- visitTypeName :: a -> Bool -> Text -> Text
- visitTypeDescription :: a -> Maybe Text -> Maybe Text
- visitFieldNames :: a -> Text -> Text
- visitEnumNames :: a -> Text -> Text
- class VisitField a where
- visitFieldName :: a -> Text -> Text
- visitFieldDescription :: a -> Maybe Text -> Maybe Text
- newtype Describe = Describe {}
- class VisitEnum a where
- visitEnumName :: a -> Text -> Text
- visitEnumDescription :: a -> Maybe Text -> Maybe Text
- typeDirective :: TypeDirectiveConstraint a => a -> DirectiveUsages
- fieldDirective :: TypeDirectiveConstraint a => FieldName -> a -> DirectiveUsages
- enumDirective :: TypeDirectiveConstraint a => TypeName -> a -> DirectiveUsages
- class (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
- newtype Deprecated = Deprecated {}
- dropNamespaceOptions :: TypeKind -> Text -> GQLTypeOptions -> GQLTypeOptions
- newtype DropNamespace = DropNamespace {}
- newtype Rename = Rename {}
Documentation
GraphQL type, every graphQL type should have an instance of Generic
and GQLType
.
... deriving (Generic, GQLType)
if you want to add description
... deriving (Generic) instance GQLType ... where description = const "your description ..."
Nothing
type KIND a :: DerivingKind #
description :: f a -> Maybe Text #
A description of the type.
Used for documentation in the GraphQL schema.
directives :: f a -> DirectiveUsages #
getDescriptions :: f a -> Map Text Description #
A dictionary of descriptions for fields, keyed on field name.
Used for documentation in the GraphQL schema.
typeOptions :: f a -> GQLTypeOptions -> GQLTypeOptions #
getDirectives :: f a -> Map Text (Directives CONST) #
Instances
class EncodeScalar a where #
GraphQL Scalar Serializer
encodeScalar :: a -> ScalarValue #
Instances
EncodeScalar ID | |
Defined in Data.Morpheus.Types.ID encodeScalar :: ID -> ScalarValue # | |
EncodeScalar Text | |
Defined in Data.Morpheus.Types.GQLScalar encodeScalar :: Text -> ScalarValue # | |
EncodeScalar Bool | |
Defined in Data.Morpheus.Types.GQLScalar encodeScalar :: Bool -> ScalarValue # | |
EncodeScalar Double | |
Defined in Data.Morpheus.Types.GQLScalar encodeScalar :: Double -> ScalarValue # | |
EncodeScalar Float | |
Defined in Data.Morpheus.Types.GQLScalar encodeScalar :: Float -> ScalarValue # | |
EncodeScalar Int | |
Defined in Data.Morpheus.Types.GQLScalar encodeScalar :: Int -> ScalarValue # |
class EncodeWrapper (wrapper :: Type -> Type) where #
GraphQL Wrapper Serializer
encodeWrapper :: Monad m => (a -> m (ResolverValue m)) -> wrapper a -> m (ResolverValue m) #
Instances
class DecodeScalar a where #
GraphQL Scalar parser
decodeScalar :: ScalarValue -> Either Text a #
Instances
DecodeScalar ID | |
Defined in Data.Morpheus.Types.ID decodeScalar :: ScalarValue -> Either Text ID # | |
DecodeScalar Text | |
Defined in Data.Morpheus.Types.GQLScalar decodeScalar :: ScalarValue -> Either Text Text # | |
DecodeScalar Bool | |
Defined in Data.Morpheus.Types.GQLScalar decodeScalar :: ScalarValue -> Either Text Bool # | |
DecodeScalar Double | |
Defined in Data.Morpheus.Types.GQLScalar decodeScalar :: ScalarValue -> Either Text Double # | |
DecodeScalar Float | |
Defined in Data.Morpheus.Types.GQLScalar decodeScalar :: ScalarValue -> Either Text Float # | |
DecodeScalar Int | |
Defined in Data.Morpheus.Types.GQLScalar decodeScalar :: ScalarValue -> Either Text Int # |
class DecodeWrapper (f :: Type -> Type) where #
GraphQL Wrapper Deserializer
decodeWrapper :: (Monad m, DecodeWrapperConstraint f a) => (ValidValue -> m a) -> ValidValue -> ExceptT GQLError m (f a) #
Instances
data GQLRequest #
GraphQL HTTP Request Body
Instances
data GQLResponse #
GraphQL Response
Instances
default GraphQL type,
parses only ScalarValue
and ScalarValue
values,
serialized always as ScalarValue
Instances
data ScalarValue #
Primitive Values for GQLScalar: ScalarValue
, ScalarValue
, ScalarValue
, Boolean
.
for performance reason type Text
represents GraphQl ScalarValue
value
Instances
data RootResolver (m :: Type -> Type) event (query :: (Type -> Type) -> Type) (mutation :: (Type -> Type) -> Type) (subscription :: (Type -> Type) -> Type) #
GraphQL Root resolver, also the interpreter generates a GQL schema from it.
queryResolver
is required, mutationResolver
and subscriptionResolver
are optional,
if your schema does not supports mutation or subscription , you can use () for it.
RootResolver | |
|
Instances
RootResolverConstraint m e query mut sub => DeriveApp RootResolver m e query mut sub | |
Defined in Data.Morpheus.Server.Deriving.App deriveApp :: RootResolver m e query mut sub -> App e m # |
constRes :: forall (o :: OperationType) (m :: Type -> Type) b a e. (WithOperation o, Monad m) => b -> a -> Resolver o e m b #
constMutRes :: Monad m => [e] -> a -> args -> ResolverM e m a Source #
data Undefined (m :: Type -> Type) #
Instances
data Resolver (o :: OperationType) event (m :: Type -> Type) value #
Instances
type SUBSCRIPTION = 'Subscription #
lift :: (MonadTrans t, Monad m) => m a -> t m a #
Lift a computation from the argument monad to the constructed monad.
liftEither :: (MonadTrans t, Monad (t m), MonadError GQLError (t m)) => Monad m => m (Either String a) -> t m a Source #
failRes :: (Monad m, WithOperation o) => String -> Resolver o e m a Source #
Deprecated: use "fail" from MonadFail
type WithOperation (o :: OperationType) = LiftOperation o #
subscribe :: forall (m :: Type -> Type) e a. Monad m => Channel e -> Resolver QUERY e m (e -> Resolver SUBSCRIPTION e m a) -> SubscriptionField (Resolver SUBSCRIPTION e m a) #
unsafeInternalContext :: forall (m :: Type -> Type) (o :: OperationType) e. (Monad m, LiftOperation o) => Resolver o e m ResolverContext #
A function to return the internal ResolverContext
within a resolver's monad.
Using the ResolverContext
itself is unsafe because it exposes internal structures
of the AST, but you can use the Data.Morpheus.Types.SelectionTree typeClass to manipulate
the internal AST with a safe interface.
data ResolverContext #
ResolverContext | |
|
Instances
Show ResolverContext | |
Defined in Data.Morpheus.App.Internal.Resolving.ResolverState showsPrec :: Int -> ResolverContext -> ShowS # show :: ResolverContext -> String # showList :: [ResolverContext] -> ShowS # | |
Monad m => MonadReader ResolverContext (ResolverStateT event m) | |
Defined in Data.Morpheus.App.Internal.Resolving.ResolverState ask :: ResolverStateT event m ResolverContext # local :: (ResolverContext -> ResolverContext) -> ResolverStateT event m a -> ResolverStateT event m a # reader :: (ResolverContext -> a) -> ResolverStateT event m a # | |
(LiftOperation o, Monad m) => MonadReader ResolverContext (Resolver o e m) | |
Defined in Data.Morpheus.App.Internal.Resolving.Resolver ask :: Resolver o e m ResolverContext # local :: (ResolverContext -> ResolverContext) -> Resolver o e m a -> Resolver o e m a # reader :: (ResolverContext -> a) -> Resolver o e m a # |
type ComposedResolver (o :: OperationType) e (m :: Type -> Type) (f :: Type -> Type) (a :: k) = Composed (Resolver o e m) f a #
type SubRes = Resolver SUBSCRIPTION Source #
Deprecated: use ResolverS
data SubscriptionField a #
Instances
Instances
render :: RenderGQL a => a -> ByteString #
data TypeGuard interface union #
ResolveInterface interface | |
ResolveType union |
Instances
(DeriveTypeConstraint OUT interface, DeriveTypeConstraint OUT union) => DeriveKindedType OUT CUSTOM (TypeGuard interface union :: Type) | |
Defined in Data.Morpheus.Server.Deriving.Schema deriveKindedType :: kinded CUSTOM (TypeGuard interface union) -> SchemaT OUT () deriveKindedContent :: kinded CUSTOM (TypeGuard interface union) -> TyContentM OUT | |
(MonadError GQLError m, EncodeConstraint m guard, EncodeConstraint m union) => EncodeKind CUSTOM m (TypeGuard guard union) | |
Defined in Data.Morpheus.Server.Deriving.Encode encodeKind :: ContextValue CUSTOM (TypeGuard guard union) -> m (ResolverValue m) | |
GQLType interface => GQLType (TypeGuard interface possibleTypes) | |
Defined in Data.Morpheus.Server.Types.GQLType type KIND (TypeGuard interface possibleTypes) :: DerivingKind # description :: f (TypeGuard interface possibleTypes) -> Maybe Text # directives :: f (TypeGuard interface possibleTypes) -> DirectiveUsages # getDescriptions :: f (TypeGuard interface possibleTypes) -> Map Text Description # typeOptions :: f (TypeGuard interface possibleTypes) -> GQLTypeOptions -> GQLTypeOptions # getDirectives :: f (TypeGuard interface possibleTypes) -> Map Text (Directives CONST) # defaultValues :: f (TypeGuard interface possibleTypes) -> Map Text (Value CONST) # __type :: f (TypeGuard interface possibleTypes) -> TypeCategory -> TypeData | |
type KIND (TypeGuard interface possibleTypes) | |
Defined in Data.Morpheus.Server.Types.GQLType |
newtype Arg (name :: Symbol) a #
Instances
Generic (Arg name a) | |
Show a => Show (Arg name a) | |
GQLType value => GQLType (Arg name value) | |
Defined in Data.Morpheus.Server.Types.GQLType type KIND (Arg name value) :: DerivingKind # description :: f (Arg name value) -> Maybe Text # directives :: f (Arg name value) -> DirectiveUsages # getDescriptions :: f (Arg name value) -> Map Text Description # typeOptions :: f (Arg name value) -> GQLTypeOptions -> GQLTypeOptions # getDirectives :: f (Arg name value) -> Map Text (Directives CONST) # defaultValues :: f (Arg name value) -> Map Text (Value CONST) # __type :: f (Arg name value) -> TypeCategory -> TypeData | |
type Rep (Arg name a) | |
Defined in Data.Morpheus.Server.Types.Types | |
type KIND (Arg name value) | |
Defined in Data.Morpheus.Server.Types.GQLType |
data NamedResolvers (m :: Type -> Type) event (qu :: (Type -> Type) -> Type) (mu :: (Type -> Type) -> Type) (su :: (Type -> Type) -> Type) #
ResolveNamed (Resolver QUERY event m) (qu (NamedResolverT (Resolver QUERY event m))) => NamedResolvers |
Instances
NamedResolversConstraint m e query mut sub => DeriveApp NamedResolvers m e query mut sub | |
Defined in Data.Morpheus.Server.Deriving.App deriveApp :: NamedResolvers m e query mut sub -> App e m # |
GQLType naming configuration
data GQLTypeOptions #
Options that specify how to map GraphQL field, type, and constructor names to and from their Haskell equivalent.
Options can be set using record syntax on defaultOptions
with the fields
below.
defaultTypeOptions :: GQLTypeOptions #
Default encoding GQLTypeOptions
:
GQLTypeOptions
{fieldLabelModifier
= id ,constructorTagModifier
= id ,typeNameModifier
= const id }
fieldLabelModifier :: GQLTypeOptions -> String -> String #
Function applied to field labels. Handy for removing common record prefixes for example.
constructorTagModifier :: GQLTypeOptions -> String -> String #
Function applied to constructor tags.
typeNameModifier :: GQLTypeOptions -> Bool -> String -> String #
Construct a new type name depending on whether it is an input, and being given the original type name.
defaultRootResolver :: forall (m :: Type -> Type) event. RootResolver m event Undefined Undefined Undefined #
GQL directives API
a custom GraphQL directive for adding or removing of prefixes
Prefixes | |
|
Instances
Nothing
visitTypeName :: a -> Bool -> Text -> Text #
Construct a new type name depending on whether it is an input, and being given the original type name.
visitTypeDescription :: a -> Maybe Text -> Maybe Text #
visitFieldNames :: a -> Text -> Text #
Function applied to field labels. Handy for removing common record prefixes for example.
visitEnumNames :: a -> Text -> Text #
Function applied to enum values Handy for removing common enum prefixes for example.
Instances
VisitType Describe | |
VisitType DropNamespace | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions visitTypeName :: DropNamespace -> Bool -> Text -> Text # visitTypeDescription :: DropNamespace -> Maybe Text -> Maybe Text # visitFieldNames :: DropNamespace -> Text -> Text # visitEnumNames :: DropNamespace -> Text -> Text # | |
VisitType Prefixes | |
VisitType Rename | |
VisitType InputTypeNamespace | |
Defined in Data.Morpheus.Server.Types.GQLType visitTypeName :: InputTypeNamespace -> Bool -> Text -> Text # visitTypeDescription :: InputTypeNamespace -> Maybe Text -> Maybe Text # visitFieldNames :: InputTypeNamespace -> Text -> Text # visitEnumNames :: InputTypeNamespace -> Text -> Text # |
class VisitField a where #
Nothing
visitFieldName :: a -> Text -> Text #
Instances
VisitField Deprecated | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions visitFieldName :: Deprecated -> Text -> Text # visitFieldDescription :: Deprecated -> Maybe Text -> Maybe Text # | |
VisitField Describe | |
VisitField Rename | |
Instances
Nothing
visitEnumName :: a -> Text -> Text #
Instances
VisitEnum Deprecated | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions visitEnumName :: Deprecated -> Text -> Text # visitEnumDescription :: Deprecated -> Maybe Text -> Maybe Text # | |
VisitEnum Describe | |
VisitEnum Rename | |
typeDirective :: TypeDirectiveConstraint a => a -> DirectiveUsages #
fieldDirective :: TypeDirectiveConstraint a => FieldName -> a -> DirectiveUsages #
enumDirective :: TypeDirectiveConstraint a => TypeName -> a -> DirectiveUsages #
default GQL directives
class (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 #
Nothing
type DIRECTIVE_LOCATIONS a :: [DirectiveLocation] #
excludeFromSchema :: f a -> Bool #
Instances
newtype Deprecated #
Instances
dropNamespaceOptions :: TypeKind -> Text -> GQLTypeOptions -> GQLTypeOptions #
newtype DropNamespace #
Instances
a custom GraphQL directive for adding or removing of prefixes
Instances
Generic Rename | |
GQLDirective Rename | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions type DIRECTIVE_LOCATIONS Rename :: [DirectiveLocation] # excludeFromSchema :: f Rename -> Bool # | |
GQLType Rename | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions type KIND Rename :: DerivingKind # description :: f Rename -> Maybe Text # directives :: f Rename -> DirectiveUsages # getDescriptions :: f Rename -> Map Text Description # typeOptions :: f Rename -> GQLTypeOptions -> GQLTypeOptions # getDirectives :: f Rename -> Map Text (Directives CONST) # defaultValues :: f Rename -> Map Text (Value CONST) # __type :: f Rename -> TypeCategory -> TypeData | |
VisitEnum Rename | |
VisitField Rename | |
VisitType Rename | |
type Rep Rename | |
type DIRECTIVE_LOCATIONS Rename | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions type DIRECTIVE_LOCATIONS Rename = '['OBJECT, 'ENUM, 'INPUT_OBJECT, 'UNION, 'SCALAR, 'INTERFACE, 'ENUM_VALUE, 'FIELD_DEFINITION, 'INPUT_FIELD_DEFINITION] | |
type KIND Rename | |