Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Data.Morpheus.Server.Types
Description
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 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
- 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
- data ResolverContext = ResolverContext {}
- 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 GQLTypeOptions
- defaultTypeOptions :: GQLTypeOptions
- fieldLabelModifier :: GQLTypeOptions -> String -> String
- constructorTagModifier :: GQLTypeOptions -> String -> String
- typeNameModifier :: GQLTypeOptions -> Bool -> String -> String
- 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
- 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
- fieldDirective' :: TypeDirectiveConstraint a => Name -> a -> DirectiveUsages
- enumDirective' :: TypeDirectiveConstraint a => Name -> 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 {}
- newtype Describe = Describe {}
- dropNamespaceOptions :: TypeKind -> Text -> GQLTypeOptions -> GQLTypeOptions
- type SCALAR = 'SCALAR
- data DerivingKind
- type TYPE = 'TYPE
- type CUSTOM = 'CUSTOM
- type WRAPPER = 'WRAPPER
- 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)
- defaultRootResolver :: RootResolver m event Undefined Undefined Undefined
- newtype Rename = Rename {}
- newtype InputTypeNamespace = InputTypeNamespace {}
- newtype DropNamespace = DropNamespace {}
Documentation
class GQLType a where Source #
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 ..."
Minimal complete definition
Nothing
Methods
description :: f a -> Maybe Text Source #
Deprecated: use: directive Describe { text } with typeDirective
A description of the type.
Used for documentation in the GraphQL schema.
directives :: f a -> DirectiveUsages Source #
getDescriptions :: f a -> Map Text Description Source #
Deprecated: use: directive Describe { text } with fieldDirective
A dictionary of descriptions for fields, keyed on field name.
Used for documentation in the GraphQL schema.
typeOptions :: f a -> GQLTypeOptions -> GQLTypeOptions Source #
Deprecated: use: custom directives with VisitType
getDirectives :: f a -> Map Text (Directives CONST) Source #
Deprecated: use: directives
Instances
class EncodeScalar a where #
GraphQL Scalar Serializer
Methods
encodeScalar :: a -> ScalarValue #
Instances
EncodeScalar ID | |
Defined in Data.Morpheus.Types.ID Methods encodeScalar :: ID -> ScalarValue # | |
EncodeScalar Text | |
Defined in Data.Morpheus.Types.GQLScalar Methods encodeScalar :: Text -> ScalarValue # | |
EncodeScalar Bool | |
Defined in Data.Morpheus.Types.GQLScalar Methods encodeScalar :: Bool -> ScalarValue # | |
EncodeScalar Double | |
Defined in Data.Morpheus.Types.GQLScalar Methods encodeScalar :: Double -> ScalarValue # | |
EncodeScalar Float | |
Defined in Data.Morpheus.Types.GQLScalar Methods encodeScalar :: Float -> ScalarValue # | |
EncodeScalar Int | |
Defined in Data.Morpheus.Types.GQLScalar Methods encodeScalar :: Int -> ScalarValue # |
class EncodeWrapper (wrapper :: Type -> Type) where #
GraphQL Wrapper Serializer
Methods
encodeWrapper :: Monad m => (a -> m (ResolverValue m)) -> wrapper a -> m (ResolverValue m) #
Instances
class DecodeScalar a where #
GraphQL Scalar parser
Methods
decodeScalar :: ScalarValue -> Either Text a #
Instances
DecodeScalar ID | |
Defined in Data.Morpheus.Types.ID Methods decodeScalar :: ScalarValue -> Either Text ID # | |
DecodeScalar Text | |
Defined in Data.Morpheus.Types.GQLScalar Methods decodeScalar :: ScalarValue -> Either Text Text # | |
DecodeScalar Bool | |
Defined in Data.Morpheus.Types.GQLScalar Methods decodeScalar :: ScalarValue -> Either Text Bool # | |
DecodeScalar Double | |
Defined in Data.Morpheus.Types.GQLScalar Methods decodeScalar :: ScalarValue -> Either Text Double # | |
DecodeScalar Float | |
Defined in Data.Morpheus.Types.GQLScalar Methods decodeScalar :: ScalarValue -> Either Text Float # | |
DecodeScalar Int | |
Defined in Data.Morpheus.Types.GQLScalar Methods decodeScalar :: ScalarValue -> Either Text Int # |
class DecodeWrapper (f :: Type -> Type) where #
GraphQL Wrapper Deserializer
Methods
decodeWrapper :: (Monad m, DecodeWrapperConstraint f a) => (ValidValue -> m a) -> ValidValue -> ExceptT GQLError m (f a) #
Instances
data GQLRequest #
GraphQL HTTP Request Body
Constructors
GQLRequest | |
Instances
data GQLResponse #
GraphQL Response
Constructors
Data ValidValue | |
Errors [GQLError] |
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 Undefined (m :: Type -> Type) Source #
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.
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 #
Constructors
ResolverContext | |
Fields
|
Instances
Show ResolverContext | |
Defined in Data.Morpheus.App.Internal.Resolving.ResolverState Methods 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 Methods 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 Methods 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 # |
data SubscriptionField a #
Instances
EncodeWrapper SubscriptionField | |
Defined in Data.Morpheus.Types.GQLWrapper Methods encodeWrapper :: Monad m => (a -> m (ResolverValue m)) -> SubscriptionField a -> m (ResolverValue m) # | |
GQLType a => GQLType (SubscriptionField a) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (SubscriptionField a) :: DerivingKind Source # Methods description :: f (SubscriptionField a) -> Maybe Text Source # directives :: f (SubscriptionField a) -> DirectiveUsages Source # getDescriptions :: f (SubscriptionField a) -> Map Text Description Source # typeOptions :: f (SubscriptionField a) -> GQLTypeOptions -> GQLTypeOptions Source # getDirectives :: f (SubscriptionField a) -> Map Text (Directives CONST) Source # defaultValues :: f (SubscriptionField a) -> Map Text (Value CONST) Source # __type :: f (SubscriptionField a) -> TypeCategory -> TypeData | |
type KIND (SubscriptionField a) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType |
Minimal complete definition
Instances
render :: RenderGQL a => a -> ByteString #
data TypeGuard interface union Source #
Constructors
ResolveInterface interface | |
ResolveType union |
Instances
GQLType interface => GQLType (TypeGuard interface possibleTypes) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (TypeGuard interface possibleTypes) :: DerivingKind Source # Methods description :: f (TypeGuard interface possibleTypes) -> Maybe Text Source # directives :: f (TypeGuard interface possibleTypes) -> DirectiveUsages Source # getDescriptions :: f (TypeGuard interface possibleTypes) -> Map Text Description Source # typeOptions :: f (TypeGuard interface possibleTypes) -> GQLTypeOptions -> GQLTypeOptions Source # getDirectives :: f (TypeGuard interface possibleTypes) -> Map Text (Directives CONST) Source # defaultValues :: f (TypeGuard interface possibleTypes) -> Map Text (Value CONST) Source # __type :: f (TypeGuard interface possibleTypes) -> TypeCategory -> TypeData | |
type KIND (TypeGuard interface possibleTypes) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType |
newtype Arg (name :: Symbol) a Source #
Instances
Generic (Arg name a) Source # | |
Show a => Show (Arg name a) Source # | |
GQLType value => GQLType (Arg name value) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Arg name value) :: DerivingKind Source # Methods description :: f (Arg name value) -> Maybe Text Source # directives :: f (Arg name value) -> DirectiveUsages Source # getDescriptions :: f (Arg name value) -> Map Text Description Source # typeOptions :: f (Arg name value) -> GQLTypeOptions -> GQLTypeOptions Source # getDirectives :: f (Arg name value) -> Map Text (Directives CONST) Source # defaultValues :: f (Arg name value) -> Map Text (Value CONST) Source # __type :: f (Arg name value) -> TypeCategory -> TypeData | |
type Rep (Arg name a) Source # | |
Defined in Data.Morpheus.Server.Types.Types | |
type KIND (Arg name value) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType |
GQLType naming configuration
data GQLTypeOptions Source #
Deprecated: use: custom directives with VisitType
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 Source #
Deprecated: use: custom directives with VisitType
Default encoding GQLTypeOptions
:
GQLTypeOptions
{fieldLabelModifier
= id ,constructorTagModifier
= id ,typeNameModifier
= const id }
fieldLabelModifier :: GQLTypeOptions -> String -> String Source #
Function applied to field labels. Handy for removing common record prefixes for example.
constructorTagModifier :: GQLTypeOptions -> String -> String Source #
Function applied to constructor tags.
typeNameModifier :: GQLTypeOptions -> Bool -> String -> String Source #
Construct a new type name depending on whether it is an input, and being given the original type name.
GQL directives API
a custom GraphQL directive for adding or removing of prefixes
Constructors
Prefixes | |
Fields
|
Instances
class VisitType a where Source #
Minimal complete definition
Nothing
Methods
visitTypeName :: a -> Bool -> Text -> Text Source #
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 Source #
visitFieldNames :: a -> Text -> Text Source #
Function applied to field labels. Handy for removing common record prefixes for example.
visitEnumNames :: a -> Text -> Text Source #
Function applied to enum values Handy for removing common enum prefixes for example.
Instances
VisitType Describe Source # | |
VisitType DropNamespace Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Methods visitTypeName :: DropNamespace -> Bool -> Text -> Text Source # visitTypeDescription :: DropNamespace -> Maybe Text -> Maybe Text Source # visitFieldNames :: DropNamespace -> Text -> Text Source # visitEnumNames :: DropNamespace -> Text -> Text Source # | |
VisitType Prefixes Source # | |
VisitType Rename Source # | |
VisitType InputTypeNamespace Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Methods visitTypeName :: InputTypeNamespace -> Bool -> Text -> Text Source # visitTypeDescription :: InputTypeNamespace -> Maybe Text -> Maybe Text Source # visitFieldNames :: InputTypeNamespace -> Text -> Text Source # visitEnumNames :: InputTypeNamespace -> Text -> Text Source # |
class VisitField a where Source #
Minimal complete definition
Nothing
Methods
visitFieldName :: a -> Text -> Text Source #
visitFieldDescription :: a -> Maybe Text -> Maybe Text Source #
Instances
VisitField Deprecated Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Methods visitFieldName :: Deprecated -> Text -> Text Source # visitFieldDescription :: Deprecated -> Maybe Text -> Maybe Text Source # | |
VisitField Describe Source # | |
VisitField Rename Source # | |
class VisitEnum a where Source #
Minimal complete definition
Nothing
Methods
visitEnumName :: a -> Text -> Text Source #
visitEnumDescription :: a -> Maybe Text -> Maybe Text Source #
Instances
VisitEnum Deprecated Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Methods visitEnumName :: Deprecated -> Text -> Text Source # visitEnumDescription :: Deprecated -> Maybe Text -> Maybe Text Source # | |
VisitEnum Describe Source # | |
VisitEnum Rename Source # | |
typeDirective :: TypeDirectiveConstraint a => a -> DirectiveUsages Source #
fieldDirective :: TypeDirectiveConstraint a => FieldName -> a -> DirectiveUsages Source #
enumDirective :: TypeDirectiveConstraint a => TypeName -> a -> DirectiveUsages Source #
fieldDirective' :: TypeDirectiveConstraint a => Name -> a -> DirectiveUsages Source #
enumDirective' :: TypeDirectiveConstraint a => Name -> a -> DirectiveUsages Source #
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 Source #
Minimal complete definition
Nothing
Associated Types
type DIRECTIVE_LOCATIONS a :: [DirectiveLocation] Source #
Methods
excludeFromSchema :: f a -> Bool Source #
Instances
newtype Deprecated Source #
Constructors
Deprecated | |
Instances
Instances
dropNamespaceOptions :: TypeKind -> Text -> GQLTypeOptions -> GQLTypeOptions Source #
Deprecated: use: custom directives
type SCALAR = 'SCALAR Source #
GraphQL Scalar: Int, Float, String, Boolean or any user defined custom Scalar type
data DerivingKind Source #
Instances
Show DerivingKind Source # | |
Defined in Data.Morpheus.Server.Types.Kind Methods showsPrec :: Int -> DerivingKind -> ShowS # show :: DerivingKind -> String # showList :: [DerivingKind] -> ShowS # |
data RootResolver (m :: Type -> Type) event (query :: (Type -> Type) -> Type) (mutation :: (Type -> Type) -> Type) (subscription :: (Type -> Type) -> Type) Source #
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.
Constructors
RootResolver | |
Fields
|
defaultRootResolver :: RootResolver m event Undefined Undefined Undefined Source #
a custom GraphQL directive for adding or removing of prefixes
Instances
newtype InputTypeNamespace Source #
Constructors
InputTypeNamespace | |
Fields |
Instances
newtype DropNamespace Source #
Constructors
DropNamespace | |
Fields |