Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Data.Morpheus.Server.Types
Description
GQL Types
Synopsis
- class GQLType a where
- type KIND a :: DerivingKind
- directives :: f a -> DirectiveUsages
- 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 = 'OPERATION_QUERY
- type MUTATION = 'OPERATION_MUTATION
- type SUBSCRIPTION = 'OPERATION_SUBSCRIPTION
- lift :: (MonadTrans t, Monad m) => m a -> t m a
- type WithOperation (o :: OperationType) = LiftOperation o
- 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 GQLError
- data Prefixes = Prefixes {
- addPrefix :: Text
- removePrefix :: Text
- data Suffixes = Suffixes {
- addSuffix :: Text
- removeSuffix :: 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
- visitFieldDefaultValue :: a -> Maybe (Value CONST) -> Maybe (Value CONST)
- class VisitEnum a where
- visitEnumName :: a -> Text -> Text
- visitEnumDescription :: a -> Maybe Text -> Maybe Text
- typeDirective :: DirectiveConstraint a => a -> DirectiveUsages
- fieldDirective :: DirectiveConstraint a => FieldName -> a -> DirectiveUsages
- enumDirective :: DirectiveConstraint a => TypeName -> a -> DirectiveUsages
- fieldDirective' :: DirectiveConstraint a => Name -> a -> DirectiveUsages
- enumDirective' :: DirectiveConstraint a => Name -> a -> DirectiveUsages
- 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
- newtype Deprecated = Deprecated {}
- newtype Describe = Describe {}
- type SCALAR = 'DERIVING_SCALAR
- data DerivingKind
- type TYPE = 'DERIVING_TYPE
- type CUSTOM = 'DERIVING_CUSTOM
- type WRAPPER = 'DERIVING_WRAPPER
- type DIRECTIVE = 'DERIVING_DIRECTIVE
- 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 {}
- newtype DefaultValue = DefaultValue {}
- data Value (stage :: Stage) where
- ResolvedVariable :: Ref FieldName -> Variable VALID -> Value 'CONST
- VariableValue :: Ref FieldName -> Value 'RAW
- Object :: forall (stage :: Stage). Object stage -> Value stage
- List :: forall (stage :: Stage). [Value stage] -> Value stage
- Enum :: forall (stage :: Stage). TypeName -> Value stage
- Scalar :: forall (stage :: Stage). ScalarValue -> Value stage
- Null :: forall (stage :: Stage). Value stage
- data DirectiveLocation
- = LOCATION_QUERY
- | LOCATION_MUTATION
- | LOCATION_SUBSCRIPTION
- | LOCATION_FIELD
- | LOCATION_FRAGMENT_DEFINITION
- | LOCATION_FRAGMENT_SPREAD
- | LOCATION_INLINE_FRAGMENT
- | LOCATION_SCHEMA
- | LOCATION_SCALAR
- | LOCATION_OBJECT
- | LOCATION_FIELD_DEFINITION
- | LOCATION_ARGUMENT_DEFINITION
- | LOCATION_INTERFACE
- | LOCATION_UNION
- | LOCATION_ENUM
- | LOCATION_ENUM_VALUE
- | LOCATION_INPUT_OBJECT
- | LOCATION_INPUT_FIELD_DEFINITION
- class (Monad m, MonadReader ResolverContext m, MonadFail m, MonadError GQLError m, Monad (MonadParam m)) => MonadResolver (m :: Type -> Type) where
- type MonadOperation (m :: Type -> Type) :: OperationType
- type MonadEvent (m :: Type -> Type)
- type MonadQuery (m :: Type -> Type) :: Type -> Type
- type MonadMutation (m :: Type -> Type) :: Type -> Type
- type MonadSubscription (m :: Type -> Type) :: Type -> Type
- type MonadParam (m :: Type -> Type) :: Type -> Type
- liftState :: ResolverState a -> m a
- getArguments :: m (Arguments VALID)
- subscribe :: MonadOperation m ~ SUBSCRIPTION => Channel (MonadEvent m) -> MonadQuery m (MonadEvent m -> m a) -> SubscriptionField (m a)
- publish :: [MonadEvent m] -> m ()
- runResolver :: Maybe (Selection VALID -> ResolverState (Channel (MonadEvent m))) -> m ValidValue -> ResolverContext -> ResponseStream (MonadEvent m) (MonadParam m) ValidValue
- class (MonadResolver m, MonadIO m) => MonadIOResolver (m :: Type -> Type)
- type family Flexible (m :: Type -> Type) a :: Type
- type family Composed (m :: Type -> Type) f a :: Type
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 directives _ = typeDirective (Describe "some text")
Minimal complete definition
Nothing
Methods
directives :: f a -> DirectiveUsages Source #
Instances
GQLType ID Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND ID :: DerivingKind Source # Methods directives :: f ID -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat ID -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c ID -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c ID -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c ID -> GQLResult (ArgumentsDefinition CONST) | |
GQLType DefaultValue Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND DefaultValue :: DerivingKind Source # Methods directives :: f DefaultValue -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat DefaultValue -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c DefaultValue -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c DefaultValue -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c DefaultValue -> GQLResult (ArgumentsDefinition CONST) | |
GQLType Deprecated Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Deprecated :: DerivingKind Source # Methods directives :: f Deprecated -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat Deprecated -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c Deprecated -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c Deprecated -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c Deprecated -> GQLResult (ArgumentsDefinition CONST) | |
GQLType Describe Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Describe :: DerivingKind Source # Methods directives :: f Describe -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat Describe -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c Describe -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c Describe -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c Describe -> GQLResult (ArgumentsDefinition CONST) | |
GQLType DropNamespace Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND DropNamespace :: DerivingKind Source # Methods directives :: f DropNamespace -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat DropNamespace -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c DropNamespace -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c DropNamespace -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c DropNamespace -> GQLResult (ArgumentsDefinition CONST) | |
GQLType Prefixes Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Prefixes :: DerivingKind Source # Methods directives :: f Prefixes -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat Prefixes -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c Prefixes -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c Prefixes -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c Prefixes -> GQLResult (ArgumentsDefinition CONST) | |
GQLType Rename Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Rename :: DerivingKind Source # Methods directives :: f Rename -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat Rename -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c Rename -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c Rename -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c Rename -> GQLResult (ArgumentsDefinition CONST) | |
GQLType Suffixes Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Suffixes :: DerivingKind Source # Methods directives :: f Suffixes -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat Suffixes -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c Suffixes -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c Suffixes -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c Suffixes -> GQLResult (ArgumentsDefinition CONST) | |
GQLType InputTypeNamespace Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND InputTypeNamespace :: DerivingKind Source # Methods directives :: f InputTypeNamespace -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat InputTypeNamespace -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c InputTypeNamespace -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c InputTypeNamespace -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c InputTypeNamespace -> GQLResult (ArgumentsDefinition CONST) | |
GQLType Text Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND Text :: DerivingKind Source # Methods directives :: f Text -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat Text -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c Text -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c Text -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c Text -> GQLResult (ArgumentsDefinition CONST) | |
GQLType () Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND () :: DerivingKind Source # Methods directives :: f () -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat () -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c () -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c () -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c () -> GQLResult (ArgumentsDefinition CONST) | |
GQLType Bool Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND Bool :: DerivingKind Source # Methods directives :: f Bool -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat Bool -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c Bool -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c Bool -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c Bool -> GQLResult (ArgumentsDefinition CONST) | |
GQLType Double Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND Double :: DerivingKind Source # Methods directives :: f Double -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat Double -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c Double -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c Double -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c Double -> GQLResult (ArgumentsDefinition CONST) | |
GQLType Float Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND Float :: DerivingKind Source # Methods directives :: f Float -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat Float -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c Float -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c Float -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c Float -> GQLResult (ArgumentsDefinition CONST) | |
GQLType Int Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND Int :: DerivingKind Source # Methods directives :: f Int -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat Int -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c Int -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c Int -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c Int -> GQLResult (ArgumentsDefinition CONST) | |
GQLType a => GQLType (NonEmpty a) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (NonEmpty a) :: DerivingKind Source # Methods directives :: f (NonEmpty a) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (NonEmpty a) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (NonEmpty a) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (NonEmpty a) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (NonEmpty a) -> GQLResult (ArgumentsDefinition CONST) | |
GQLType a => GQLType (Seq a) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Seq a) :: DerivingKind Source # Methods directives :: f (Seq a) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (Seq a) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (Seq a) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (Seq a) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Seq a) -> GQLResult (ArgumentsDefinition CONST) | |
GQLType a => GQLType (Set a) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Set a) :: DerivingKind Source # Methods directives :: f (Set a) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (Set a) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (Set a) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (Set a) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Set a) -> GQLResult (ArgumentsDefinition CONST) | |
GQLType a => GQLType (SubscriptionField a) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (SubscriptionField a) :: DerivingKind Source # Methods directives :: f (SubscriptionField a) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (SubscriptionField a) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (SubscriptionField a) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (SubscriptionField a) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (SubscriptionField a) -> GQLResult (ArgumentsDefinition CONST) | |
GQLType (Value CONST) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Methods directives :: f (Value CONST) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (Value CONST) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (Value CONST) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (Value CONST) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Value CONST) -> GQLResult (ArgumentsDefinition CONST) | |
Typeable m => GQLType (Undefined m) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Undefined m) :: DerivingKind Source # Methods directives :: f (Undefined m) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (Undefined m) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (Undefined m) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (Undefined m) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Undefined m) -> GQLResult (ArgumentsDefinition CONST) | |
GQLType a => GQLType (Vector a) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Vector a) :: DerivingKind Source # Methods directives :: f (Vector a) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (Vector a) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (Vector a) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (Vector a) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Vector a) -> GQLResult (ArgumentsDefinition CONST) | |
GQLType a => GQLType (Maybe a) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Maybe a) :: DerivingKind Source # Methods directives :: f (Maybe a) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (Maybe a) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (Maybe a) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (Maybe a) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Maybe a) -> GQLResult (ArgumentsDefinition CONST) | |
GQLType a => GQLType [a] Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND [a] :: DerivingKind Source # Methods directives :: f [a] -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat [a] -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c [a] -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c [a] -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c [a] -> GQLResult (ArgumentsDefinition CONST) | |
(GQLType k, GQLType v, Typeable k, Typeable v) => GQLType (Map k v) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Map k v) :: DerivingKind Source # Methods directives :: f (Map k v) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (Map k v) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (Map k v) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (Map k v) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Map k v) -> GQLResult (ArgumentsDefinition CONST) | |
GQLType a => GQLType (NamedResolverT m a) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (NamedResolverT m a) :: DerivingKind Source # Methods directives :: f (NamedResolverT m a) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (NamedResolverT m a) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (NamedResolverT m a) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (NamedResolverT m a) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (NamedResolverT m a) -> GQLResult (ArgumentsDefinition CONST) | |
(KnownSymbol name, GQLType value) => GQLType (Arg name value) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Arg name value) :: DerivingKind Source # Methods directives :: f (Arg name value) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (Arg name value) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (Arg name value) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (Arg name value) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Arg name value) -> GQLResult (ArgumentsDefinition CONST) | |
(DERIVE_TYPE GQLType i, DERIVE_TYPE GQLType u) => GQLType (TypeGuard i u) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (TypeGuard i u) :: DerivingKind Source # Methods directives :: f (TypeGuard i u) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (TypeGuard i u) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (TypeGuard i u) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (TypeGuard i u) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (TypeGuard i u) -> GQLResult (ArgumentsDefinition CONST) | |
(Typeable k, Typeable v, GQLType k, GQLType v) => GQLType (k, v) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (k, v) :: DerivingKind Source # Methods directives :: f (k, v) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (k, v) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (k, v) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (k, v) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (k, v) -> GQLResult (ArgumentsDefinition CONST) | |
(GQLType b, GQLType a, Gmap GQLType (Rep a)) => GQLType (a -> b) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (a -> b) :: DerivingKind Source # Methods directives :: f (a -> b) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (a -> b) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (a -> b) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (a -> b) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (a -> b) -> GQLResult (ArgumentsDefinition CONST) | |
GQLType a => GQLType (Resolver o e m a) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Resolver o e m a) :: DerivingKind Source # Methods directives :: f (Resolver o e m a) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (Resolver o e m a) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (Resolver o e m a) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (Resolver o e m a) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Resolver o e m a) -> GQLResult (ArgumentsDefinition CONST) |
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 QUERY = 'OPERATION_QUERY #
type MUTATION = 'OPERATION_MUTATION #
type SUBSCRIPTION = 'OPERATION_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 #
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 directives :: f (SubscriptionField a) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (SubscriptionField a) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (SubscriptionField a) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (SubscriptionField a) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (SubscriptionField a) -> GQLResult (ArgumentsDefinition CONST) | |
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
(DERIVE_TYPE GQLType i, DERIVE_TYPE GQLType u) => GQLType (TypeGuard i u) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (TypeGuard i u) :: DerivingKind Source # Methods directives :: f (TypeGuard i u) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (TypeGuard i u) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (TypeGuard i u) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (TypeGuard i u) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (TypeGuard i u) -> GQLResult (ArgumentsDefinition CONST) | |
type KIND (TypeGuard i u) 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 # | |
(KnownSymbol name, GQLType value) => GQLType (Arg name value) Source # | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Arg name value) :: DerivingKind Source # Methods directives :: f (Arg name value) -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat (Arg name value) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (Arg name value) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (Arg name value) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Arg name value) -> GQLResult (ArgumentsDefinition CONST) | |
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 |
Instances
GQL directives API
a custom GraphQL directive for adding or removing of prefixes
Constructors
Prefixes | |
Fields
|
Instances
a custom GraphQL directive for adding or removing of suffixes
Constructors
Suffixes | |
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 Suffixes 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 #
visitFieldDefaultValue :: a -> Maybe (Value CONST) -> Maybe (Value CONST) Source #
Instances
VisitField DefaultValue Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Methods visitFieldName :: DefaultValue -> Text -> Text Source # visitFieldDescription :: DefaultValue -> Maybe Text -> Maybe Text Source # visitFieldDefaultValue :: DefaultValue -> Maybe (Value CONST) -> Maybe (Value CONST) Source # | |
VisitField Deprecated Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Methods visitFieldName :: Deprecated -> Text -> Text Source # visitFieldDescription :: Deprecated -> Maybe Text -> Maybe Text Source # visitFieldDefaultValue :: Deprecated -> Maybe (Value CONST) -> Maybe (Value CONST) 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 :: DirectiveConstraint a => a -> DirectiveUsages Source #
fieldDirective :: DirectiveConstraint a => FieldName -> a -> DirectiveUsages Source #
enumDirective :: DirectiveConstraint a => TypeName -> a -> DirectiveUsages Source #
fieldDirective' :: DirectiveConstraint a => Name -> a -> DirectiveUsages Source #
enumDirective' :: DirectiveConstraint a => Name -> a -> DirectiveUsages Source #
default GQL directives
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 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
type SCALAR = 'DERIVING_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
Generic Rename Source # | |
GQLDirective Rename Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type DIRECTIVE_LOCATIONS Rename :: [DirectiveLocation] Source # Methods excludeFromSchema :: f Rename -> Bool Source # | |
GQLType Rename Source # | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Rename :: DerivingKind Source # Methods directives :: f Rename -> DirectiveUsages Source # __type :: forall (cat :: TypeCategory). CatType cat Rename -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c Rename -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c Rename -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c Rename -> GQLResult (ArgumentsDefinition CONST) | |
VisitEnum Rename Source # | |
VisitField Rename Source # | |
VisitType Rename Source # | |
type Rep Rename Source # | |
type DIRECTIVE_LOCATIONS Rename Source # | |
type KIND Rename Source # | |
newtype InputTypeNamespace Source #
Constructors
InputTypeNamespace | |
Fields |
Instances
newtype DropNamespace Source #
Constructors
DropNamespace | |
Fields |
Instances
newtype DefaultValue Source #
Constructors
DefaultValue | |
Fields |
Instances
data Value (stage :: Stage) where #
Constructors
ResolvedVariable :: Ref FieldName -> Variable VALID -> Value 'CONST | |
VariableValue :: Ref FieldName -> Value 'RAW | |
Object :: forall (stage :: Stage). Object stage -> Value stage | |
List :: forall (stage :: Stage). [Value stage] -> Value stage | |
Enum :: forall (stage :: Stage). TypeName -> Value stage | |
Scalar :: forall (stage :: Stage). ScalarValue -> Value stage | |
Null :: forall (stage :: Stage). Value stage |
Instances
data DirectiveLocation #
Constructors
Instances
Show DirectiveLocation | |
Defined in Data.Morpheus.Types.Internal.AST.DirectiveLocation Methods showsPrec :: Int -> DirectiveLocation -> ShowS # show :: DirectiveLocation -> String # showList :: [DirectiveLocation] -> ShowS # | |
Eq DirectiveLocation | |
Defined in Data.Morpheus.Types.Internal.AST.DirectiveLocation Methods (==) :: DirectiveLocation -> DirectiveLocation -> Bool # (/=) :: DirectiveLocation -> DirectiveLocation -> Bool # | |
RenderGQL DirectiveLocation | |
Defined in Data.Morpheus.Types.Internal.AST.DirectiveLocation Methods renderGQL :: DirectiveLocation -> Rendering # | |
Msg DirectiveLocation | |
Defined in Data.Morpheus.Types.Internal.AST.DirectiveLocation Methods msg :: DirectiveLocation -> GQLError # | |
Lift DirectiveLocation | |
Defined in Data.Morpheus.Types.Internal.AST.DirectiveLocation Methods lift :: Quote m => DirectiveLocation -> m Exp # liftTyped :: forall (m :: Type -> Type). Quote m => DirectiveLocation -> Code m DirectiveLocation # |
class (Monad m, MonadReader ResolverContext m, MonadFail m, MonadError GQLError m, Monad (MonadParam m)) => MonadResolver (m :: Type -> Type) where #
Associated Types
type MonadOperation (m :: Type -> Type) :: OperationType #
type MonadEvent (m :: Type -> Type) #
type MonadQuery (m :: Type -> Type) :: Type -> Type #
type MonadMutation (m :: Type -> Type) :: Type -> Type #
type MonadSubscription (m :: Type -> Type) :: Type -> Type #
Methods
liftState :: ResolverState a -> m a #
getArguments :: m (Arguments VALID) #
subscribe :: MonadOperation m ~ SUBSCRIPTION => Channel (MonadEvent m) -> MonadQuery m (MonadEvent m -> m a) -> SubscriptionField (m a) #
publish :: [MonadEvent m] -> m () #
runResolver :: Maybe (Selection VALID -> ResolverState (Channel (MonadEvent m))) -> m ValidValue -> ResolverContext -> ResponseStream (MonadEvent m) (MonadParam m) ValidValue #
Instances
class (MonadResolver m, MonadIO m) => MonadIOResolver (m :: Type -> Type) #
Instances
(LiftOperation o, Monad m, MonadIO m) => MonadIOResolver (Resolver o e m) | |