| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Data.Morpheus.Types
Description
GQL Types
Synopsis
- 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 :: * -> *) event (query :: (* -> *) -> *) (mut :: (* -> *) -> *) (sub :: (* -> *) -> *) = GQLRootResolver {- queryResolver :: query (Resolver QUERY m event)
- mutationResolver :: mut (Resolver MUTATION m event)
- subscriptionResolver :: sub (Resolver SUBSCRIPTION m event)
 
- constRes :: (PureOperation o, Monad m) => b -> a -> Resolver o m e b
- constMutRes :: Monad m => [e] -> a -> args -> MutRes m e a
- data Undefined (m :: * -> *) = Undefined
- type Res = Resolver QUERY
- type MutRes = Resolver MUTATION
- type SubRes = Resolver SUBSCRIPTION
- type IORes = Res IO
- type IOMutRes = MutRes IO
- type IOSubRes = SubRes IO
- data Resolver (o :: OperationType) (m :: * -> *) event value where- FailedResolver :: {..} -> Resolver o m event value
- QueryResolver :: {..} -> Resolver QUERY m event value
- MutResolver :: {..} -> Resolver MUTATION m event value
- SubResolver :: {..} -> Resolver SUBSCRIPTION m event value
 
- type QUERY = Query
- type MUTATION = Mutation
- type SUBSCRIPTION = Subscription
- liftEitherM :: (PureOperation o, Monad m) => m (Either String a) -> Resolver o m e a
- liftM :: (PureOperation o, Monad m) => m a -> Resolver o m e a
Documentation
class GQLType a where Source #
GraphQL type, every graphQL type should have an instance of Generic and GQLType.
... deriving (Generic, GQLType)
if you want to add description
      ... deriving (Generic)
    instance GQLType ... where
      description = const "your description ..."
 Minimal complete definition
Nothing
Instances
class GQLScalar a where Source #
GraphQL Scalar
parseValue and serialize should be provided for every instances manually
Methods
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
Constructors
| GQLRequest | |
Instances
| Show GQLRequest Source # | |
| Defined in Data.Morpheus.Types.IO Methods showsPrec :: Int -> GQLRequest -> ShowS # show :: GQLRequest -> String # showList :: [GQLRequest] -> ShowS # | |
| Generic GQLRequest Source # | |
| Defined in Data.Morpheus.Types.IO Associated Types type Rep GQLRequest :: Type -> Type # | |
| ToJSON GQLRequest Source # | |
| Defined in Data.Morpheus.Types.IO Methods toJSON :: GQLRequest -> Value # toEncoding :: GQLRequest -> Encoding # toJSONList :: [GQLRequest] -> Value # toEncodingList :: [GQLRequest] -> Encoding # | |
| FromJSON GQLRequest Source # | |
| Defined in Data.Morpheus.Types.IO | |
| Interpreter (GQLRequest -> m GQLResponse) m e Source # | |
| Defined in Data.Morpheus.Execution.Server.Interpreter Methods interpreter :: (Monad m, RootResCon m e query mut sub) => GQLRootResolver m e query mut sub -> GQLRequest -> m GQLResponse Source # | |
| type Rep GQLRequest Source # | |
| Defined in Data.Morpheus.Types.IO | |
data GQLResponse Source #
GraphQL Response
Instances
| Show GQLResponse Source # | |
| Defined in Data.Morpheus.Types.IO Methods showsPrec :: Int -> GQLResponse -> ShowS # show :: GQLResponse -> String # showList :: [GQLResponse] -> ShowS # | |
| Generic GQLResponse Source # | |
| Defined in Data.Morpheus.Types.IO Associated Types type Rep GQLResponse :: Type -> Type # | |
| ToJSON GQLResponse Source # | |
| Defined in Data.Morpheus.Types.IO Methods toJSON :: GQLResponse -> Value # toEncoding :: GQLResponse -> Encoding # toJSONList :: [GQLResponse] -> Value # toEncodingList :: [GQLResponse] -> Encoding # | |
| FromJSON GQLResponse Source # | |
| Defined in Data.Morpheus.Types.IO | |
| Interpreter (GQLRequest -> m GQLResponse) m e Source # | |
| Defined in Data.Morpheus.Execution.Server.Interpreter Methods interpreter :: (Monad m, RootResCon m e query mut sub) => GQLRootResolver m e query mut sub -> GQLRequest -> m GQLResponse Source # | |
| type Rep GQLResponse Source # | |
| Defined in Data.Morpheus.Types.IO | |
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 Methods 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 :: * -> *) event (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.
Constructors
| GQLRootResolver | |
| Fields 
 | |
constMutRes :: Monad m => [e] -> a -> args -> MutRes m e a Source #
data Undefined (m :: * -> *) Source #
Constructors
| Undefined | 
type SubRes = Resolver SUBSCRIPTION Source #
data Resolver (o :: OperationType) (m :: * -> *) event value where Source #
Constructors
| FailedResolver | |
| Fields 
 | |
| QueryResolver | |
| Fields 
 | |
| MutResolver | |
| SubResolver | |
| Fields 
 | |
Instances
| Monad m => Monad (Resolver QUERY m e) Source # | |
| Functor m => Functor (Resolver o m e) Source # | |
| (PureOperation o, Monad m) => Applicative (Resolver o m e) Source # | |
| Defined in Data.Morpheus.Types.Internal.Resolver Methods pure :: a -> Resolver o m e a # (<*>) :: Resolver o m e (a -> b) -> Resolver o m e a -> Resolver o m e b # liftA2 :: (a -> b -> c) -> Resolver o m e a -> Resolver o m e b -> Resolver o m e c # (*>) :: Resolver o m e a -> Resolver o m e b -> Resolver o m e b # (<*) :: Resolver o m e a -> Resolver o m e b -> Resolver o m e a # | |
| GQLType a => GQLType (Resolver o m e a) Source # | |
| Defined in Data.Morpheus.Types.GQLType Methods description :: Proxy (Resolver o m e a) -> Maybe Text Source # __typeName :: Proxy (Resolver o m e a) -> Text __typeFingerprint :: Proxy (Resolver o m e a) -> DataFingerprint | |
| type KIND (Resolver o m e a) Source # | |
| Defined in Data.Morpheus.Types.GQLType | |
type SUBSCRIPTION = Subscription Source #