morpheus-graphql-server-0.27.3: Morpheus GraphQL
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Morpheus.Server.Types

Description

GQL Types

Synopsis

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

Associated Types

type KIND a :: DerivingKind Source #

type KIND a = TYPE

Methods

directives :: f a -> DirectiveUsages Source #

Instances

Instances details
GQLType ID Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c ID -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType DefaultValue Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c DefaultValue -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType Deprecated Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Deprecated -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType Describe Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Describe -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType DropNamespace Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c DropNamespace -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType Prefixes Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Prefixes -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType Rename Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Rename -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType InputTypeNamespace Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c InputTypeNamespace -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType Text Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Text -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType () Source # 
Instance details

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 () -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c () -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType Bool Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Bool -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType Double Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Double -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType Float Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Float -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType Int Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Int -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType a => GQLType (Seq a) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Seq a) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType a => GQLType (Set a) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Set a) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType a => GQLType (SubscriptionField a) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (SubscriptionField a) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType (Value CONST) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

Associated Types

type KIND (Value CONST) :: DerivingKind Source #

Methods

directives :: f (Value CONST) -> DirectiveUsages Source #

__type :: forall (cat :: TypeCategory). CatType cat (Value CONST) -> TypeData

__deriveType :: forall (c :: TypeCategory). CatType c (Value CONST) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Value CONST) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

Typeable m => GQLType (Undefined m) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Undefined m) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType a => GQLType (Vector a) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Vector a) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType a => GQLType (NonEmpty a) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (NonEmpty a) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType a => GQLType (Maybe a) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Maybe a) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType a => GQLType [a] Source # 
Instance details

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] -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c [a] -> SchemaT c (Maybe (ArgumentsDefinition CONST))

(GQLType k, GQLType v, Typeable k, Typeable v) => GQLType (Map k v) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Map k v) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType a => GQLType (NamedResolverT m a) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (NamedResolverT m a) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

(KnownSymbol name, GQLType value) => GQLType (Arg name value) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Arg name value) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

(DERIVE_TYPE GQLType OUT i, DERIVE_TYPE GQLType OUT u) => GQLType (TypeGuard i u) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (TypeGuard i u) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

(GQLType b, GQLType a) => GQLType (a -> b) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (a -> b) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

(Typeable a, Typeable b, GQLType a, GQLType b) => GQLType (a, b) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (a, b) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

GQLType a => GQLType (Resolver o e m a) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Resolver o e m a) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

class EncodeScalar a where #

GraphQL Scalar Serializer

Methods

encodeScalar :: a -> ScalarValue #

Instances

Instances details
EncodeScalar ID 
Instance details

Defined in Data.Morpheus.Types.ID

EncodeScalar Text 
Instance details

Defined in Data.Morpheus.Types.GQLScalar

EncodeScalar Bool 
Instance details

Defined in Data.Morpheus.Types.GQLScalar

EncodeScalar Double 
Instance details

Defined in Data.Morpheus.Types.GQLScalar

EncodeScalar Float 
Instance details

Defined in Data.Morpheus.Types.GQLScalar

EncodeScalar Int 
Instance details

Defined in Data.Morpheus.Types.GQLScalar

class EncodeWrapper (wrapper :: Type -> Type) where #

GraphQL Wrapper Serializer

Methods

encodeWrapper :: Monad m => (a -> m (ResolverValue m)) -> wrapper a -> m (ResolverValue m) #

Instances

Instances details
EncodeWrapper Seq 
Instance details

Defined in Data.Morpheus.Types.GQLWrapper

Methods

encodeWrapper :: Monad m => (a -> m (ResolverValue m)) -> Seq a -> m (ResolverValue m) #

EncodeWrapper Set 
Instance details

Defined in Data.Morpheus.Types.GQLWrapper

Methods

encodeWrapper :: Monad m => (a -> m (ResolverValue m)) -> Set a -> m (ResolverValue m) #

EncodeWrapper SubscriptionField 
Instance details

Defined in Data.Morpheus.Types.GQLWrapper

Methods

encodeWrapper :: Monad m => (a -> m (ResolverValue m)) -> SubscriptionField a -> m (ResolverValue m) #

EncodeWrapper Vector 
Instance details

Defined in Data.Morpheus.Types.GQLWrapper

Methods

encodeWrapper :: Monad m => (a -> m (ResolverValue m)) -> Vector a -> m (ResolverValue m) #

EncodeWrapper NonEmpty 
Instance details

Defined in Data.Morpheus.Types.GQLWrapper

Methods

encodeWrapper :: Monad m => (a -> m (ResolverValue m)) -> NonEmpty a -> m (ResolverValue m) #

EncodeWrapper Maybe 
Instance details

Defined in Data.Morpheus.Types.GQLWrapper

Methods

encodeWrapper :: Monad m => (a -> m (ResolverValue m)) -> Maybe a -> m (ResolverValue m) #

EncodeWrapper [] 
Instance details

Defined in Data.Morpheus.Types.GQLWrapper

Methods

encodeWrapper :: Monad m => (a -> m (ResolverValue m)) -> [a] -> m (ResolverValue m) #

class DecodeScalar a where #

GraphQL Scalar parser

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) #

data GQLRequest #

GraphQL HTTP Request Body

Instances

Instances details
FromJSON GQLRequest 
Instance details

Defined in Data.Morpheus.Types.IO

ToJSON GQLRequest 
Instance details

Defined in Data.Morpheus.Types.IO

Generic GQLRequest 
Instance details

Defined in Data.Morpheus.Types.IO

Associated Types

type Rep GQLRequest :: Type -> Type #

Show GQLRequest 
Instance details

Defined in Data.Morpheus.Types.IO

MapAPI GQLRequest GQLResponse 
Instance details

Defined in Data.Morpheus.App.MapAPI

type Rep GQLRequest 
Instance details

Defined in Data.Morpheus.Types.IO

type Rep GQLRequest = D1 ('MetaData "GQLRequest" "Data.Morpheus.Types.IO" "morpheus-graphql-core-0.27.3-7plQmdT9PxpJTKqPgX8pDL" 'False) (C1 ('MetaCons "GQLRequest" 'PrefixI 'True) (S1 ('MetaSel ('Just "operationName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe FieldName)) :*: (S1 ('MetaSel ('Just "query") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "variables") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Value)))))

data GQLResponse #

GraphQL Response

Constructors

Data ValidValue 
Errors [GQLError] 

Instances

Instances details
FromJSON GQLResponse 
Instance details

Defined in Data.Morpheus.Types.IO

ToJSON GQLResponse 
Instance details

Defined in Data.Morpheus.Types.IO

Generic GQLResponse 
Instance details

Defined in Data.Morpheus.Types.IO

Associated Types

type Rep GQLResponse :: Type -> Type #

Show GQLResponse 
Instance details

Defined in Data.Morpheus.Types.IO

MapAPI GQLRequest GQLResponse 
Instance details

Defined in Data.Morpheus.App.MapAPI

type Rep GQLResponse 
Instance details

Defined in Data.Morpheus.Types.IO

type Rep GQLResponse = D1 ('MetaData "GQLResponse" "Data.Morpheus.Types.IO" "morpheus-graphql-core-0.27.3-7plQmdT9PxpJTKqPgX8pDL" 'False) (C1 ('MetaCons "Data" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 ValidValue)) :+: C1 ('MetaCons "Errors" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [GQLError])))

newtype ID #

default GraphQL type, parses only ScalarValue and ScalarValue values, serialized always as ScalarValue

Constructors

ID 

Fields

Instances

Instances details
FromJSON ID 
Instance details

Defined in Data.Morpheus.Types.ID

ToJSON ID 
Instance details

Defined in Data.Morpheus.Types.ID

IsString ID 
Instance details

Defined in Data.Morpheus.Types.ID

Methods

fromString :: String -> ID #

Semigroup ID 
Instance details

Defined in Data.Morpheus.Types.ID

Methods

(<>) :: ID -> ID -> ID #

sconcat :: NonEmpty ID -> ID #

stimes :: Integral b => b -> ID -> ID #

Generic ID 
Instance details

Defined in Data.Morpheus.Types.ID

Associated Types

type Rep ID :: Type -> Type #

Methods

from :: ID -> Rep ID x #

to :: Rep ID x -> ID #

Show ID 
Instance details

Defined in Data.Morpheus.Types.ID

Methods

showsPrec :: Int -> ID -> ShowS #

show :: ID -> String #

showList :: [ID] -> ShowS #

Eq ID 
Instance details

Defined in Data.Morpheus.Types.ID

Methods

(==) :: ID -> ID -> Bool #

(/=) :: ID -> ID -> Bool #

Hashable ID 
Instance details

Defined in Data.Morpheus.Types.ID

Methods

hashWithSalt :: Int -> ID -> Int #

hash :: ID -> Int #

DecodeScalar ID 
Instance details

Defined in Data.Morpheus.Types.ID

EncodeScalar ID 
Instance details

Defined in Data.Morpheus.Types.ID

GQLType ID Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c ID -> SchemaT c (Maybe (ArgumentsDefinition CONST))

ResolveNamed m ID Source # 
Instance details

Defined in Data.Morpheus.Server.Types.NamedResolvers

Associated Types

type Dep ID Source #

Methods

resolveBatched :: [Dependency ID] -> m [Maybe ID] Source #

resolveNamed :: Dependency ID -> m ID Source #

type Rep ID 
Instance details

Defined in Data.Morpheus.Types.ID

type Rep ID = D1 ('MetaData "ID" "Data.Morpheus.Types.ID" "morpheus-graphql-core-0.27.3-7plQmdT9PxpJTKqPgX8pDL" 'True) (C1 ('MetaCons "ID" 'PrefixI 'True) (S1 ('MetaSel ('Just "unpackID") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type KIND ID Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

type KIND ID = SCALAR
type Dep ID Source # 
Instance details

Defined in Data.Morpheus.Server.Types.NamedResolvers

type Dep ID = ID

data ScalarValue #

Primitive Values for GQLScalar: ScalarValue, ScalarValue, ScalarValue, Boolean. for performance reason type Text represents GraphQl ScalarValue value

Instances

Instances details
FromJSON ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

ToJSON ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

IsString ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Generic ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Associated Types

type Rep ScalarValue :: Type -> Type #

Show ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Eq ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

RenderGQL ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

renderGQL :: ScalarValue -> Rendering #

Lift ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

lift :: Quote m => ScalarValue -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => ScalarValue -> Code m ScalarValue #

type Rep ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

data Undefined (m :: Type -> Type) Source #

Instances

Instances details
Generic (Undefined m) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.Types

Associated Types

type Rep (Undefined m) :: Type -> Type #

Methods

from :: Undefined m -> Rep (Undefined m) x #

to :: Rep (Undefined m) x -> Undefined m #

Show (Undefined m) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.Types

Typeable m => GQLType (Undefined m) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Undefined m) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

type Rep (Undefined m) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.Types

type Rep (Undefined m) = D1 ('MetaData "Undefined" "Data.Morpheus.Server.Types.Types" "morpheus-graphql-server-0.27.3-E3obHu3ivEuJiqvyXXXqgf" 'True) (C1 ('MetaCons "Undefined" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))
type KIND (Undefined m) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

type KIND (Undefined m) = TYPE

data Resolver (o :: OperationType) event (m :: Type -> Type) value #

Instances

Instances details
Monad m => PushEvents e (Resolver MUTATION e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Methods

pushEvents :: [e] -> Resolver MUTATION e m () #

(LiftOperation o, Monad m) => MonadError GQLError (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Methods

throwError :: GQLError -> Resolver o e m a #

catchError :: Resolver o e m a -> (GQLError -> Resolver o e m a) -> Resolver o e m a #

(LiftOperation o, Monad m) => MonadReader ResolverContext (Resolver o e m) 
Instance details

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 #

LiftOperation o => MonadTrans (Resolver o e) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Methods

lift :: Monad m => m a -> Resolver o e m a #

(Monad m, LiftOperation o) => MonadFail (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Methods

fail :: String -> Resolver o e m a #

(MonadIO m, LiftOperation o) => MonadIO (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Methods

liftIO :: IO a -> Resolver o e m a #

(LiftOperation o, Monad m) => Applicative (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Methods

pure :: a -> Resolver o e m a #

(<*>) :: Resolver o e m (a -> b) -> Resolver o e m a -> Resolver o e m b #

liftA2 :: (a -> b -> c) -> Resolver o e m a -> Resolver o e m b -> Resolver o e m c #

(*>) :: Resolver o e m a -> Resolver o e m b -> Resolver o e m b #

(<*) :: Resolver o e m a -> Resolver o e m b -> Resolver o e m a #

Functor m => Functor (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Methods

fmap :: (a -> b) -> Resolver o e m a -> Resolver o e m b #

(<$) :: a -> Resolver o e m b -> Resolver o e m a #

(Monad m, LiftOperation o) => Monad (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Methods

(>>=) :: Resolver o e m a -> (a -> Resolver o e m b) -> Resolver o e m b #

(>>) :: Resolver o e m a -> Resolver o e m b -> Resolver o e m b #

return :: a -> Resolver o e m a #

(LiftOperation o, Monad m, MonadIO m) => MonadIOResolver (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

(LiftOperation o, Monad m) => MonadResolver (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Associated Types

type MonadOperation (Resolver o e m) :: OperationType #

type MonadEvent (Resolver o e m) #

type MonadQuery (Resolver o e m) :: Type -> Type #

type MonadMutation (Resolver o e m) :: Type -> Type #

type MonadSubscription (Resolver o e m) :: Type -> Type #

type MonadParam (Resolver o e m) :: Type -> Type #

(Monad m, Semigroup a, LiftOperation o) => Semigroup (Resolver o e m a) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Methods

(<>) :: Resolver o e m a -> Resolver o e m a -> Resolver o e m a #

sconcat :: NonEmpty (Resolver o e m a) -> Resolver o e m a #

stimes :: Integral b => b -> Resolver o e m a -> Resolver o e m a #

Show (Resolver o e m value) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Methods

showsPrec :: Int -> Resolver o e m value -> ShowS #

show :: Resolver o e m value -> String #

showList :: [Resolver o e m value] -> ShowS #

GQLType a => GQLType (Resolver o e m a) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Resolver o e m a) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

type MonadEvent (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

type MonadEvent (Resolver o e m) = e
type MonadMutation (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

type MonadOperation (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

type MonadOperation (Resolver o e m) = o
type MonadParam (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

type MonadParam (Resolver o e m) = m
type MonadQuery (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

type MonadQuery (Resolver o e m) = Resolver QUERY e m
type MonadSubscription (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

type KIND (Resolver o e m a) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

type KIND (Resolver o e m a) = CUSTOM

lift :: (MonadTrans t, Monad m) => m a -> t m a #

Lift a computation from the argument monad to the constructed monad.

data ResolverContext #

Instances

Instances details
Show ResolverContext 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.ResolverState

Monad m => MonadReader ResolverContext (ResolverStateT event m) 
Instance details

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) 
Instance details

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

Instances details
EncodeWrapper SubscriptionField 
Instance details

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 # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (SubscriptionField a) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

type KIND (SubscriptionField a) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

data App event (m :: Type -> Type) #

Instances

Instances details
Monad m => Semigroup (App e m) 
Instance details

Defined in Data.Morpheus.App

Methods

(<>) :: App e m -> App e m -> App e m #

sconcat :: NonEmpty (App e m) -> App e m #

stimes :: Integral b => b -> App e m -> App e m #

RenderGQL (App e m) 
Instance details

Defined in Data.Morpheus.App

Methods

renderGQL :: App e m -> Rendering #

class RenderGQL a #

Minimal complete definition

renderGQL

Instances

Instances details
RenderGQL Value 
Instance details

Defined in Data.Morpheus.Rendering.RenderGQL

Methods

renderGQL :: Value -> Rendering #

RenderGQL ByteString 
Instance details

Defined in Data.Morpheus.Rendering.RenderGQL

Methods

renderGQL :: ByteString -> Rendering #

RenderGQL DirectiveLocation 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.DirectiveLocation

Methods

renderGQL :: DirectiveLocation -> Rendering #

RenderGQL OperationType 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.OperationType

Methods

renderGQL :: OperationType -> Rendering #

RenderGQL UnionTag 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Selection

Methods

renderGQL :: UnionTag -> Rendering #

RenderGQL TypeKind 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Type

Methods

renderGQL :: TypeKind -> Rendering #

RenderGQL TypeRef 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Type

Methods

renderGQL :: TypeRef -> Rendering #

RenderGQL RootOperationTypeDefinition 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.TypeSystem

Methods

renderGQL :: RootOperationTypeDefinition -> Rendering #

RenderGQL SchemaDefinition 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.TypeSystem

Methods

renderGQL :: SchemaDefinition -> Rendering #

RenderGQL ScalarValue 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

renderGQL :: ScalarValue -> Rendering #

RenderGQL Text 
Instance details

Defined in Data.Morpheus.Rendering.RenderGQL

Methods

renderGQL :: Text -> Rendering #

RenderGQL Bool 
Instance details

Defined in Data.Morpheus.Rendering.RenderGQL

Methods

renderGQL :: Bool -> Rendering #

RenderGQL Double 
Instance details

Defined in Data.Morpheus.Rendering.RenderGQL

Methods

renderGQL :: Double -> Rendering #

RenderGQL Float 
Instance details

Defined in Data.Morpheus.Rendering.RenderGQL

Methods

renderGQL :: Float -> Rendering #

RenderGQL Int 
Instance details

Defined in Data.Morpheus.Rendering.RenderGQL

Methods

renderGQL :: Int -> Rendering #

RenderGQL (Argument s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

Methods

renderGQL :: Argument s -> Rendering #

RenderGQL (ArgumentDefinition s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

Methods

renderGQL :: ArgumentDefinition s -> Rendering #

RenderGQL (ArgumentsDefinition s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

Methods

renderGQL :: ArgumentsDefinition s -> Rendering #

RenderGQL (Directive s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

Methods

renderGQL :: Directive s -> Rendering #

RenderGQL (DirectiveDefinition s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

Methods

renderGQL :: DirectiveDefinition s -> Rendering #

RenderGQL (Directives s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

Methods

renderGQL :: Directives s -> Rendering #

RenderGQL (Name a) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Name

Methods

renderGQL :: Name a -> Rendering #

RenderGQL (Operation VALID) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Selection

Methods

renderGQL :: Operation VALID -> Rendering #

RenderGQL (Selection VALID) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Selection

Methods

renderGQL :: Selection VALID -> Rendering #

RenderGQL (SelectionContent VALID) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Selection

Methods

renderGQL :: SelectionContent VALID -> Rendering #

RenderGQL (DataEnumValue s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.TypeSystem

Methods

renderGQL :: DataEnumValue s -> Rendering #

RenderGQL (Schema s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.TypeSystem

Methods

renderGQL :: Schema s -> Rendering #

RenderGQL (ObjectEntry a) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

renderGQL :: ObjectEntry a -> Rendering #

RenderGQL (Value a) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

renderGQL :: Value a -> Rendering #

RenderGQL a => RenderGQL (Maybe a) 
Instance details

Defined in Data.Morpheus.Rendering.RenderGQL

Methods

renderGQL :: Maybe a -> Rendering #

(RenderGQL l, RenderGQL r) => RenderGQL (Either l r) 
Instance details

Defined in Data.Morpheus.Rendering.RenderGQL

Methods

renderGQL :: Either l r -> Rendering #

RenderGQL (App e m) 
Instance details

Defined in Data.Morpheus.App

Methods

renderGQL :: App e m -> Rendering #

RenderGQL (FieldDefinition cat s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

Methods

renderGQL :: FieldDefinition cat s -> Rendering #

RenderGQL (FieldsDefinition cat s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

Methods

renderGQL :: FieldsDefinition cat s -> Rendering #

RenderGQL (TypeDefinition a s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.TypeSystem

Methods

renderGQL :: TypeDefinition a s -> Rendering #

RenderGQL (UnionMember cat s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Union

Methods

renderGQL :: UnionMember cat s -> Rendering #

RenderGQL (AppData e m s) 
Instance details

Defined in Data.Morpheus.App

Methods

renderGQL :: AppData e m s -> Rendering #

data TypeGuard interface union Source #

Constructors

ResolveInterface interface 
ResolveType union 

Instances

Instances details
(DERIVE_TYPE GQLType OUT i, DERIVE_TYPE GQLType OUT u) => GQLType (TypeGuard i u) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (TypeGuard i u) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

type KIND (TypeGuard i u) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

type KIND (TypeGuard i u) = CUSTOM

newtype Arg (name :: Symbol) a Source #

Constructors

Arg 

Fields

Instances

Instances details
Generic (Arg name a) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.Types

Associated Types

type Rep (Arg name a) :: Type -> Type #

Methods

from :: Arg name a -> Rep (Arg name a) x #

to :: Rep (Arg name a) x -> Arg name a #

Show a => Show (Arg name a) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.Types

Methods

showsPrec :: Int -> Arg name a -> ShowS #

show :: Arg name a -> String #

showList :: [Arg name a] -> ShowS #

(KnownSymbol name, GQLType value) => GQLType (Arg name value) Source # 
Instance details

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) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Arg name value) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

type Rep (Arg name a) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.Types

type Rep (Arg name a) = D1 ('MetaData "Arg" "Data.Morpheus.Server.Types.Types" "morpheus-graphql-server-0.27.3-E3obHu3ivEuJiqvyXXXqgf" 'True) (C1 ('MetaCons "Arg" 'PrefixI 'True) (S1 ('MetaSel ('Just "argValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type KIND (Arg name value) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

type KIND (Arg name value) = CUSTOM

data GQLError #

Instances

Instances details
FromJSON GQLError 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Error

ToJSON GQLError 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Error

IsString GQLError 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Error

Semigroup GQLError 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Error

Generic GQLError 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Error

Associated Types

type Rep GQLError :: Type -> Type #

Methods

from :: GQLError -> Rep GQLError x #

to :: Rep GQLError x -> GQLError #

Show GQLError 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Error

Eq GQLError 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Error

Ord GQLError 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Error

Msg GQLError 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Error

Methods

msg :: GQLError -> GQLError #

NameCollision GQLError RootOperationTypeDefinition 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.TypeSystem

NameCollision GQLError SchemaDefinition 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.TypeSystem

NameCollision GQLError (Argument s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

NameCollision GQLError (ArgumentDefinition s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

NameCollision GQLError (Directive s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

NameCollision GQLError (DirectiveDefinition s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

NameCollision GQLError (Fragment s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Selection

NameCollision GQLError (ObjectEntry s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

NameCollision GQLError (Variable s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

NameCollision GQLError (FieldDefinition cat s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Fields

NameCollision GQLError (TypeDefinition cat s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.TypeSystem

NameCollision GQLError (UnionMember c s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Union

Monad m => MonadError GQLError (ResolverStateT e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.ResolverState

Methods

throwError :: GQLError -> ResolverStateT e m a #

catchError :: ResolverStateT e m a -> (GQLError -> ResolverStateT e m a) -> ResolverStateT e m a #

Monad m => MonadError GQLError (ResultT event m) 
Instance details

Defined in Data.Morpheus.Ext.Result

Methods

throwError :: GQLError -> ResultT event m a #

catchError :: ResultT event m a -> (GQLError -> ResultT event m a) -> ResultT event m a #

(LiftOperation o, Monad m) => MonadError GQLError (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Methods

throwError :: GQLError -> Resolver o e m a #

catchError :: Resolver o e m a -> (GQLError -> Resolver o e m a) -> Resolver o e m a #

type Rep GQLError 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Error

type Rep GQLError = D1 ('MetaData "GQLError" "Data.Morpheus.Types.Internal.AST.Error" "morpheus-graphql-core-0.27.3-7plQmdT9PxpJTKqPgX8pDL" 'False) (C1 ('MetaCons "GQLError" 'PrefixI 'True) ((S1 ('MetaSel ('Just "message") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Message) :*: S1 ('MetaSel ('Just "locations") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [Position]))) :*: (S1 ('MetaSel ('Just "path") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe [PropName])) :*: (S1 ('MetaSel ('Just "errorType") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe ErrorType)) :*: S1 ('MetaSel ('Just "extensions") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (Map Text Value)))))))

GQL directives API

data Prefixes Source #

a custom GraphQL directive for adding or removing of prefixes

Constructors

Prefixes 

Instances

Instances details
Generic Prefixes Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

Associated Types

type Rep Prefixes :: Type -> Type #

Methods

from :: Prefixes -> Rep Prefixes x #

to :: Rep Prefixes x -> Prefixes #

GQLDirective Prefixes Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

GQLType Prefixes Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Prefixes -> SchemaT c (Maybe (ArgumentsDefinition CONST))

VisitType Prefixes Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type Rep Prefixes Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type Rep Prefixes = D1 ('MetaData "Prefixes" "Data.Morpheus.Server.Types.DirectiveDefinitions" "morpheus-graphql-server-0.27.3-E3obHu3ivEuJiqvyXXXqgf" 'False) (C1 ('MetaCons "Prefixes" 'PrefixI 'True) (S1 ('MetaSel ('Just "addPrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text) :*: S1 ('MetaSel ('Just "removePrefix") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type DIRECTIVE_LOCATIONS Prefixes Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type KIND Prefixes Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

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

Instances details
VisitType Describe Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

VisitType DropNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

VisitType Prefixes Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

VisitType Rename Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

VisitType InputTypeNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

class VisitField a where Source #

Minimal complete definition

Nothing

typeDirective :: (GQLDirective a, gql a, args a) => a -> GDirectiveUsages gql args Source #

fieldDirective :: (GQLDirective a, gql a, args a) => FieldName -> a -> GDirectiveUsages gql args Source #

enumDirective :: (GQLDirective a, gql a, args a) => TypeName -> a -> GDirectiveUsages gql args Source #

fieldDirective' :: (GQLDirective a, gql a, args a) => Name -> a -> GDirectiveUsages gql args Source #

enumDirective' :: (GQLDirective a, gql a, args a) => Name -> a -> GDirectiveUsages gql args 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

Instances details
GQLDirective DefaultValue Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

GQLDirective Deprecated Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

GQLDirective Describe Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

GQLDirective DropNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

GQLDirective Prefixes Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

GQLDirective Rename Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

GQLDirective InputTypeNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

newtype Deprecated Source #

Constructors

Deprecated 

Fields

Instances

Instances details
Generic Deprecated Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

Associated Types

type Rep Deprecated :: Type -> Type #

GQLDirective Deprecated Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

GQLType Deprecated Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Deprecated -> SchemaT c (Maybe (ArgumentsDefinition CONST))

VisitEnum Deprecated Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

VisitField Deprecated Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type Rep Deprecated Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type Rep Deprecated = D1 ('MetaData "Deprecated" "Data.Morpheus.Server.Types.DirectiveDefinitions" "morpheus-graphql-server-0.27.3-E3obHu3ivEuJiqvyXXXqgf" 'True) (C1 ('MetaCons "Deprecated" 'PrefixI 'True) (S1 ('MetaSel ('Just "reason") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Text))))
type DIRECTIVE_LOCATIONS Deprecated Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type KIND Deprecated Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

newtype Describe Source #

Constructors

Describe 

Fields

Instances

Instances details
Generic Describe Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

Associated Types

type Rep Describe :: Type -> Type #

Methods

from :: Describe -> Rep Describe x #

to :: Rep Describe x -> Describe #

GQLDirective Describe Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

GQLType Describe Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Describe -> SchemaT c (Maybe (ArgumentsDefinition CONST))

VisitEnum Describe Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

VisitField Describe Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

VisitType Describe Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type Rep Describe Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type Rep Describe = D1 ('MetaData "Describe" "Data.Morpheus.Server.Types.DirectiveDefinitions" "morpheus-graphql-server-0.27.3-E3obHu3ivEuJiqvyXXXqgf" 'True) (C1 ('MetaCons "Describe" 'PrefixI 'True) (S1 ('MetaSel ('Just "text") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type DIRECTIVE_LOCATIONS Describe Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type KIND Describe Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type SCALAR = 'DERIVING_SCALAR Source #

GraphQL Scalar: Int, Float, String, Boolean or any user defined custom Scalar type

data DerivingKind Source #

Instances

Instances details
Show DerivingKind Source # 
Instance details

Defined in Data.Morpheus.Server.Types.Kind

type TYPE = 'DERIVING_TYPE Source #

GraphQL input, type, union , enum

type CUSTOM = 'DERIVING_CUSTOM Source #

type WRAPPER = 'DERIVING_WRAPPER Source #

GraphQL Arrays , Resolvers and NonNull fields

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

newtype Rename Source #

a custom GraphQL directive for adding or removing of prefixes

Constructors

Rename 

Fields

Instances

Instances details
Generic Rename Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

Associated Types

type Rep Rename :: Type -> Type #

Methods

from :: Rename -> Rep Rename x #

to :: Rep Rename x -> Rename #

GQLDirective Rename Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

GQLType Rename Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c Rename -> SchemaT c (Maybe (ArgumentsDefinition CONST))

VisitEnum Rename Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

VisitField Rename Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

VisitType Rename Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type Rep Rename Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type Rep Rename = D1 ('MetaData "Rename" "Data.Morpheus.Server.Types.DirectiveDefinitions" "morpheus-graphql-server-0.27.3-E3obHu3ivEuJiqvyXXXqgf" 'True) (C1 ('MetaCons "Rename" 'PrefixI 'True) (S1 ('MetaSel ('Just "newName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type DIRECTIVE_LOCATIONS Rename Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type KIND Rename Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

newtype InputTypeNamespace Source #

Instances

Instances details
Generic InputTypeNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

Associated Types

type Rep InputTypeNamespace :: Type -> Type #

GQLDirective InputTypeNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

GQLType InputTypeNamespace Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c InputTypeNamespace -> SchemaT c (Maybe (ArgumentsDefinition CONST))

VisitType InputTypeNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

type Rep InputTypeNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

type Rep InputTypeNamespace = D1 ('MetaData "InputTypeNamespace" "Data.Morpheus.Server.Types.GQLType" "morpheus-graphql-server-0.27.3-E3obHu3ivEuJiqvyXXXqgf" 'True) (C1 ('MetaCons "InputTypeNamespace" 'PrefixI 'True) (S1 ('MetaSel ('Just "inputTypeNamespace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type DIRECTIVE_LOCATIONS InputTypeNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

type KIND InputTypeNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

newtype DropNamespace Source #

Constructors

DropNamespace 

Fields

Instances

Instances details
Generic DropNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

Associated Types

type Rep DropNamespace :: Type -> Type #

GQLDirective DropNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

GQLType DropNamespace Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c DropNamespace -> SchemaT c (Maybe (ArgumentsDefinition CONST))

VisitType DropNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type Rep DropNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type Rep DropNamespace = D1 ('MetaData "DropNamespace" "Data.Morpheus.Server.Types.DirectiveDefinitions" "morpheus-graphql-server-0.27.3-E3obHu3ivEuJiqvyXXXqgf" 'True) (C1 ('MetaCons "DropNamespace" 'PrefixI 'True) (S1 ('MetaSel ('Just "dropNamespace") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)))
type DIRECTIVE_LOCATIONS DropNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type KIND DropNamespace Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

newtype DefaultValue Source #

Constructors

DefaultValue 

Instances

Instances details
Generic DefaultValue Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

Associated Types

type Rep DefaultValue :: Type -> Type #

GQLDirective DefaultValue Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

GQLType DefaultValue Source # 
Instance details

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 -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c DefaultValue -> SchemaT c (Maybe (ArgumentsDefinition CONST))

VisitField DefaultValue Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type Rep DefaultValue Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type Rep DefaultValue = D1 ('MetaData "DefaultValue" "Data.Morpheus.Server.Types.DirectiveDefinitions" "morpheus-graphql-server-0.27.3-E3obHu3ivEuJiqvyXXXqgf" 'True) (C1 ('MetaCons "DefaultValue" 'PrefixI 'True) (S1 ('MetaSel ('Just "defaultValue") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Value CONST))))
type DIRECTIVE_LOCATIONS DefaultValue Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

type KIND DefaultValue Source # 
Instance details

Defined in Data.Morpheus.Server.Types.DirectiveDefinitions

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

Instances details
Lift (Value a :: Type) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

lift :: Quote m => Value a -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => Value a -> Code m (Value a) #

FromJSON (Value a) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

ToJSON (Value a) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

IsString (Value stage) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

fromString :: String -> Value stage #

Show (Value a) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

showsPrec :: Int -> Value a -> ShowS #

show :: Value a -> String #

showList :: [Value a] -> ShowS #

Eq (Value s) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

(==) :: Value s -> Value s -> Bool #

(/=) :: Value s -> Value s -> Bool #

Hashable (Value a) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

hashWithSalt :: Int -> Value a -> Int #

hash :: Value a -> Int #

RenderGQL (Value a) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

renderGQL :: Value a -> Rendering #

Msg (Value a) 
Instance details

Defined in Data.Morpheus.Types.Internal.AST.Value

Methods

msg :: Value a -> GQLError #

GQLType (Value CONST) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

Associated Types

type KIND (Value CONST) :: DerivingKind Source #

Methods

directives :: f (Value CONST) -> DirectiveUsages Source #

__type :: forall (cat :: TypeCategory). CatType cat (Value CONST) -> TypeData

__deriveType :: forall (c :: TypeCategory). CatType c (Value CONST) -> SchemaT c (TypeDefinition c CONST)

__deriveFieldArguments :: forall (c :: TypeCategory). CatType c (Value CONST) -> SchemaT c (Maybe (ArgumentsDefinition CONST))

type KIND (Value CONST) Source # 
Instance details

Defined in Data.Morpheus.Server.Types.GQLType

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 #

type MonadParam (m :: Type -> Type) :: Type -> Type #

Instances

Instances details
(LiftOperation o, Monad m) => MonadResolver (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

Associated Types

type MonadOperation (Resolver o e m) :: OperationType #

type MonadEvent (Resolver o e m) #

type MonadQuery (Resolver o e m) :: Type -> Type #

type MonadMutation (Resolver o e m) :: Type -> Type #

type MonadSubscription (Resolver o e m) :: Type -> Type #

type MonadParam (Resolver o e m) :: Type -> Type #

class (MonadResolver m, MonadIO m) => MonadIOResolver (m :: Type -> Type) #

Instances

Instances details
(LiftOperation o, Monad m, MonadIO m) => MonadIOResolver (Resolver o e m) 
Instance details

Defined in Data.Morpheus.App.Internal.Resolving.Resolver

type family Flexible (m :: Type -> Type) a :: Type Source #

Instances

Instances details
type Flexible m (a :: Type) Source # 
Instance details

Defined in Data.Morpheus.Server.Resolvers

type Flexible m (a :: Type) = m a
type Flexible m (a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Morpheus.Server.Resolvers

type Flexible m (a :: (Type -> Type) -> Type) = m (a m)

type family Composed (m :: Type -> Type) f a :: Type Source #

Instances

Instances details
type Composed m f (a :: Type) Source # 
Instance details

Defined in Data.Morpheus.Server.Resolvers

type Composed m f (a :: Type) = m (f a)
type Composed m f (a :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Data.Morpheus.Server.Resolvers

type Composed m f (a :: (Type -> Type) -> Type) = m (f (a m))