Safe Haskell | None |
---|---|
Language | Haskell2010 |
GQL Types
Synopsis
- resolver :: m (Either String a) -> Resolver m a
- mutResolver :: Monad m => [Event e c] -> StreamT m (Event e c) (Either String a) -> MutResolver m e c a
- toMutResolver :: Monad m => [Event e c] -> Resolver m a -> MutResolver m e c a
- type IORes = Resolver IO
- type IOMutRes e c = MutResolver IO e c
- type IOSubRes e c = SubResolver IO e c
- type Resolver = ExceptT String
- type SubRootRes m e sub = Resolver (SubscribeStream m e) sub
- data SubResolver m e c a = SubResolver {
- subChannels :: [e]
- subResolver :: Event e c -> Resolver m a
- data Event e c = Event {}
- class GQLType a where
- class GQLScalar a where
- parseValue :: ScalarValue -> Either Text a
- serialize :: a -> ScalarValue
- data GQLRequest = GQLRequest {}
- data GQLResponse
- newtype ID = ID {}
- data ScalarValue
- data GQLRootResolver m e c query mut sub = GQLRootResolver {
- queryResolver :: Resolver m query
- mutationResolver :: Resolver (PublishStream m e c) mut
- subscriptionResolver :: SubRootRes m e sub
- constRes :: Monad m => b -> a -> m b
Documentation
mutResolver :: Monad m => [Event e c] -> StreamT m (Event e c) (Either String a) -> MutResolver m e c a Source #
GraphQL Resolver for mutation or subscription resolver , adds effect to normal resolver
type IOSubRes e c = SubResolver IO e c Source #
type SubRootRes m e sub = Resolver (SubscribeStream m e) sub Source #
data SubResolver m e c a Source #
SubResolver | |
|
Instances
GQLType a => GQLType (SubResolver m e c a) Source # | |
Defined in Data.Morpheus.Types.GQLType type KIND (SubResolver m e c a) :: GQL_KIND Source # type CUSTOM (SubResolver m e c a) :: Bool description :: Proxy (SubResolver m e c a) -> Maybe Text Source # __typeVisibility :: Proxy (SubResolver m e c a) -> Bool __typeName :: Proxy (SubResolver m e c a) -> Text __typeFingerprint :: Proxy (SubResolver m e c a) -> DataFingerprint | |
type KIND (SubResolver m e c a) Source # | |
Defined in Data.Morpheus.Types.GQLType |
class GQLType a where Source #
GraphQL type, every graphQL type should have an instance of Generic
and GQLType
.
... deriving (Generic, GQLType)
if you want to add description
... deriving (Generic) instance GQLType ... where description = const "your description ..."
Nothing
Instances
class GQLScalar a where Source #
GraphQL Scalar
parseValue
and serialize
should be provided for every instances manually
parseValue :: ScalarValue -> Either Text a Source #
value parsing and validating
for exhaustive pattern matching should be handled all scalar types : ScalarValue
, ScalarValue
, ScalarValue
, Boolean
invalid values can be reported with Left
constructor :
parseValue String _ = Left "" -- without error message -- or parseValue String _ = Left "Error Message"
serialize :: a -> ScalarValue Source #
serialization of haskell type into scalar value
Instances
data GQLRequest Source #
GraphQL HTTP Request Body
Instances
data GQLResponse Source #
GraphQL Response
Instances
default GraphQL type,
parses only ScalarValue
and ScalarValue
values,
serialized always as ScalarValue
Instances
Show ID Source # | |
Generic ID Source # | |
GQLScalar ID Source # | |
Defined in Data.Morpheus.Types.ID parseValue :: ScalarValue -> Either Text ID Source # serialize :: ID -> ScalarValue Source # scalarValidator :: Proxy ID -> DataValidator | |
GQLType ID Source # | |
type Rep ID Source # | |
Defined in Data.Morpheus.Types.ID | |
type KIND ID Source # | |
Defined in Data.Morpheus.Types.ID |
data ScalarValue Source #
Primitive Values for GQLScalar: ScalarValue
, ScalarValue
, ScalarValue
, Boolean
.
for performance reason type Text
represents GraphQl ScalarValue
value
Instances
data GQLRootResolver m e c query mut sub 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 acn use () for it.
GQLRootResolver | |
|