Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Data.Morpheus.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 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 :: MonadResolver m => b -> a -> m b
- 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
- liftEither :: (MonadTrans t, Monad (t m), MonadError GQLError (t m)) => Monad m => m (Either String a) -> t m a
- type WithOperation (o :: OperationType) = LiftOperation o
- 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) = ResolverO QUERY e m a
- type ResolverM e (m :: Type -> Type) (a :: k) = ResolverO MUTATION e m a
- type ResolverS e (m :: Type -> Type) (a :: k) = ResolverO SUBSCRIPTION e m a
- 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
- defaultRootResolver :: forall (m :: Type -> Type) event. RootResolver m event Undefined Undefined Undefined
- 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)
- newtype Describe = Describe {}
- 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
- 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 DropNamespace = DropNamespace {}
- newtype Rename = Rename {}
- newtype DefaultValue = DefaultValue {}
- data GQLError
- class Monad m => MonadError e (m :: Type -> Type) | m -> e
- 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 :: k)
- type family Composed (m :: Type -> Type) (f :: Type -> Type) (a :: k)
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 directives _ = typeDirective (Describe "some text")
Minimal complete definition
Nothing
Methods
directives :: f a -> DirectiveUsages #
Instances
GQLType ID | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND ID :: DerivingKind # Methods directives :: f ID -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND DefaultValue :: DerivingKind # Methods directives :: f DefaultValue -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Deprecated :: DerivingKind # Methods directives :: f Deprecated -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Describe :: DerivingKind # Methods directives :: f Describe -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND DropNamespace :: DerivingKind # Methods directives :: f DropNamespace -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Prefixes :: DerivingKind # Methods directives :: f Prefixes -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Rename :: DerivingKind # Methods directives :: f Rename -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Suffixes :: DerivingKind # Methods directives :: f Suffixes -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND InputTypeNamespace :: DerivingKind # Methods directives :: f InputTypeNamespace -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND Text :: DerivingKind # Methods directives :: f Text -> DirectiveUsages # __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 () | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND () :: DerivingKind # Methods directives :: f () -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND Bool :: DerivingKind # Methods directives :: f Bool -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND Double :: DerivingKind # Methods directives :: f Double -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND Float :: DerivingKind # Methods directives :: f Float -> DirectiveUsages # __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 | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND Int :: DerivingKind # Methods directives :: f Int -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (NonEmpty a) :: DerivingKind # Methods directives :: f (NonEmpty a) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Seq a) :: DerivingKind # Methods directives :: f (Seq a) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Set a) :: DerivingKind # Methods directives :: f (Set a) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (SubscriptionField a) :: DerivingKind # Methods directives :: f (SubscriptionField a) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Value CONST) :: DerivingKind # Methods directives :: f (Value CONST) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Undefined m) :: DerivingKind # Methods directives :: f (Undefined m) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Vector a) :: DerivingKind # Methods directives :: f (Vector a) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Maybe a) :: DerivingKind # Methods directives :: f (Maybe a) -> DirectiveUsages # __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] | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND [a] :: DerivingKind # Methods directives :: f [a] -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Map k v) :: DerivingKind # Methods directives :: f (Map k v) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (NamedResolverT m a) :: DerivingKind # Methods directives :: f (NamedResolverT m a) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Arg name value) :: DerivingKind # Methods directives :: f (Arg name value) -> DirectiveUsages # __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) | |
(Typeable a, Typeable b, GQLType a, GQLType b) => GQLType (Pair a b) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Pair a b) :: DerivingKind # Methods directives :: f (Pair a b) -> DirectiveUsages # __type :: forall (cat :: TypeCategory). CatType cat (Pair a b) -> TypeData __deriveType :: forall (c :: TypeCategory). CatType c (Pair a b) -> GQLResult (GQLTypeNode c) __exploreRef :: forall (c :: TypeCategory). CatType c (Pair a b) -> [ScanRef FreeCatType GQLType] __deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Pair a b) -> GQLResult (ArgumentsDefinition CONST) | |
(DERIVE_TYPE GQLType i, DERIVE_TYPE GQLType u) => GQLType (TypeGuard i u) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (TypeGuard i u) :: DerivingKind # Methods directives :: f (TypeGuard i u) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (k, v) :: DerivingKind # Methods directives :: f (k, v) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (a -> b) :: DerivingKind # Methods directives :: f (a -> b) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Resolver o e m a) :: DerivingKind # Methods directives :: f (Resolver o e m a) -> DirectiveUsages # __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 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.
Constructors
RootResolver | |
Fields
|
Instances
RootResolverConstraint m e query mut sub => DeriveApp RootResolver m e query mut sub | |
Defined in Data.Morpheus.Server.Deriving.App Methods deriveApp :: RootResolver m e query mut sub -> App e m # |
constRes :: MonadResolver m => b -> a -> m b #
data Undefined (m :: Type -> Type) #
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.
liftEither :: (MonadTrans t, Monad (t m), MonadError GQLError (t m)) => Monad m => m (Either String a) -> t m a Source #
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 # |
type ComposedResolver (o :: OperationType) e (m :: Type -> Type) (f :: Type -> Type) (a :: k) = Composed (Resolver o e m) f 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) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (SubscriptionField a) :: DerivingKind # Methods directives :: f (SubscriptionField a) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType |
Minimal complete definition
Instances
render :: RenderGQL a => a -> ByteString #
data TypeGuard interface union #
Constructors
ResolveInterface interface | |
ResolveType union |
Instances
(DERIVE_TYPE GQLType i, DERIVE_TYPE GQLType u) => GQLType (TypeGuard i u) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (TypeGuard i u) :: DerivingKind # Methods directives :: f (TypeGuard i u) -> DirectiveUsages # __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) | |
Defined in Data.Morpheus.Server.Types.GQLType |
newtype Arg (name :: Symbol) a #
Instances
Generic (Arg name a) | |
Show a => Show (Arg name a) | |
(KnownSymbol name, GQLType value) => GQLType (Arg name value) | |
Defined in Data.Morpheus.Server.Types.GQLType Associated Types type KIND (Arg name value) :: DerivingKind # Methods directives :: f (Arg name value) -> DirectiveUsages # __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) | |
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) #
Constructors
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 Methods deriveApp :: NamedResolvers m e query mut sub -> App e m # |
GQLType naming configuration
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
Constructors
Prefixes | |
Fields
|
Instances
a custom GraphQL directive for adding or removing of suffixes
Constructors
Suffixes | |
Fields
|
Instances
Minimal complete definition
Nothing
Methods
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 Methods visitTypeName :: DropNamespace -> Bool -> Text -> Text # visitTypeDescription :: DropNamespace -> Maybe Text -> Maybe Text # visitFieldNames :: DropNamespace -> Text -> Text # visitEnumNames :: DropNamespace -> Text -> Text # | |
VisitType Prefixes | |
VisitType Rename | |
VisitType Suffixes | |
VisitType InputTypeNamespace | |
Defined in Data.Morpheus.Server.Types.GQLType Methods visitTypeName :: InputTypeNamespace -> Bool -> Text -> Text # visitTypeDescription :: InputTypeNamespace -> Maybe Text -> Maybe Text # visitFieldNames :: InputTypeNamespace -> Text -> Text # visitEnumNames :: InputTypeNamespace -> Text -> Text # |
class VisitField a where #
Minimal complete definition
Nothing
Methods
visitFieldName :: a -> Text -> Text #
visitFieldDescription :: a -> Maybe Text -> Maybe Text #
visitFieldDefaultValue :: a -> Maybe (Value CONST) -> Maybe (Value CONST) #
Instances
VisitField DefaultValue | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Methods visitFieldName :: DefaultValue -> Text -> Text # visitFieldDescription :: DefaultValue -> Maybe Text -> Maybe Text # visitFieldDefaultValue :: DefaultValue -> Maybe (Value CONST) -> Maybe (Value CONST) # | |
VisitField Deprecated | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Methods visitFieldName :: Deprecated -> Text -> Text # visitFieldDescription :: Deprecated -> Maybe Text -> Maybe Text # visitFieldDefaultValue :: Deprecated -> Maybe (Value CONST) -> Maybe (Value CONST) # | |
VisitField Describe | |
VisitField Rename | |
Instances
Generic Describe | |
GQLDirective Describe | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type DIRECTIVE_LOCATIONS Describe :: [DirectiveLocation] # Methods excludeFromSchema :: f Describe -> Bool # | |
GQLType Describe | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Describe :: DerivingKind # Methods directives :: f Describe -> DirectiveUsages # __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) | |
VisitEnum Describe | |
VisitField Describe | |
VisitType Describe | |
type Rep Describe | |
type DIRECTIVE_LOCATIONS Describe | |
type KIND Describe | |
Minimal complete definition
Nothing
Instances
VisitEnum Deprecated | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Methods visitEnumName :: Deprecated -> Text -> Text # visitEnumDescription :: Deprecated -> Maybe Text -> Maybe Text # | |
VisitEnum Describe | |
VisitEnum Rename | |
typeDirective :: DirectiveConstraint a => a -> DirectiveUsages #
fieldDirective :: DirectiveConstraint a => FieldName -> a -> DirectiveUsages #
enumDirective :: DirectiveConstraint a => TypeName -> a -> DirectiveUsages #
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 #
Minimal complete definition
Nothing
Associated Types
type DIRECTIVE_LOCATIONS a :: [DirectiveLocation] #
Methods
excludeFromSchema :: f a -> Bool #
Instances
newtype Deprecated #
Constructors
Deprecated | |
Instances
newtype DropNamespace #
Constructors
DropNamespace | |
Fields |
Instances
a custom GraphQL directive for adding or removing of prefixes
Instances
Generic Rename | |
GQLDirective Rename | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type DIRECTIVE_LOCATIONS Rename :: [DirectiveLocation] # Methods excludeFromSchema :: f Rename -> Bool # | |
GQLType Rename | |
Defined in Data.Morpheus.Server.Types.DirectiveDefinitions Associated Types type KIND Rename :: DerivingKind # Methods directives :: f Rename -> DirectiveUsages # __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 | |
VisitField Rename | |
VisitType Rename | |
type Rep Rename | |
type DIRECTIVE_LOCATIONS Rename | |
type KIND Rename | |
newtype DefaultValue #
Constructors
DefaultValue | |
Fields |
Instances
Instances
class Monad m => MonadError e (m :: Type -> Type) | m -> e #
The strategy of combining computations that can throw exceptions by bypassing bound functions from the point an exception is thrown to the point that it is handled.
Is parameterized over the type of error information and
the monad type constructor.
It is common to use
as the monad type constructor
for an error monad in which error descriptions take the form of strings.
In that case and many other common cases the resulting monad is already defined
as an instance of the Either
StringMonadError
class.
You can also define your own error type and/or use a monad type constructor
other than
or Either
String
.
In these cases you will have to explicitly define instances of the Either
IOError
MonadError
class.
(If you are using the deprecated Control.Monad.Error or
Control.Monad.Trans.Error, you may also have to define an Error
instance.)
Minimal complete definition
Instances
data DirectiveLocation #
Constructors
Instances
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) | |