Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module allows you to server a Mu Server
as a WAI Application
using GraphQL.
The simples way is to use runGraphQLAppQuery
(if you only provide GraphQL queries) or
runGraphQLApp
(if you also have mutations
or subscriptions). All other variants provide
more control over the settings.
Synopsis
- type GraphQLApp p qr mut sub m chn hs = (ParseTypedDoc p qr mut sub, RunDocument p qr mut sub m chn hs)
- runGraphQLApp :: GraphQLApp p qr mut sub ServerErrorIO chn hs => Port -> ServerT chn Field p ServerErrorIO hs -> Proxy qr -> Proxy mut -> Proxy sub -> IO ()
- runGraphQLAppSettings :: GraphQLApp p qr mut sub ServerErrorIO chn hs => Settings -> ServerT chn Field p ServerErrorIO hs -> Proxy qr -> Proxy mut -> Proxy sub -> IO ()
- runGraphQLAppQuery :: GraphQLApp p ('Just qr) 'Nothing 'Nothing ServerErrorIO chn hs => Port -> ServerT chn Field p ServerErrorIO hs -> Proxy qr -> IO ()
- runGraphQLAppTrans :: GraphQLApp p qr mut sub m chn hs => Port -> (forall a. m a -> ServerErrorIO a) -> ServerT chn Field p m hs -> Proxy qr -> Proxy mut -> Proxy sub -> IO ()
- graphQLApp :: GraphQLApp p qr mut sub ServerErrorIO chn hs => ServerT chn Field p ServerErrorIO hs -> Proxy qr -> Proxy mut -> Proxy sub -> Application
- graphQLAppQuery :: forall qr p chn hs. GraphQLApp p ('Just qr) 'Nothing 'Nothing ServerErrorIO chn hs => ServerT chn Field p ServerErrorIO hs -> Proxy qr -> Application
- graphQLAppTrans :: GraphQLApp p qr mut sub m chn hs => (forall a. m a -> ServerErrorIO a) -> ServerT chn Field p m hs -> Proxy qr -> Proxy mut -> Proxy sub -> Application
- graphQLAppTransQuery :: forall qr m p chn hs. GraphQLApp p ('Just qr) 'Nothing 'Nothing m chn hs => (forall a. m a -> ServerErrorIO a) -> ServerT chn Field p m hs -> Proxy qr -> Application
- liftServerConduit :: MonadIO m => ConduitT i o ServerErrorIO r -> ConduitT i o m r
Documentation
type GraphQLApp p qr mut sub m chn hs = (ParseTypedDoc p qr mut sub, RunDocument p qr mut sub m chn hs) Source #
Run an GraphQL resolver directly
runGraphQLApp :: GraphQLApp p qr mut sub ServerErrorIO chn hs => Port -> ServerT chn Field p ServerErrorIO hs -> Proxy qr -> Proxy mut -> Proxy sub -> IO () Source #
Run a Mu graphQLApp
on the given port.
runGraphQLAppSettings :: GraphQLApp p qr mut sub ServerErrorIO chn hs => Settings -> ServerT chn Field p ServerErrorIO hs -> Proxy qr -> Proxy mut -> Proxy sub -> IO () Source #
Run a Mu graphQLApp
using the given Settings
.
runGraphQLAppQuery :: GraphQLApp p ('Just qr) 'Nothing 'Nothing ServerErrorIO chn hs => Port -> ServerT chn Field p ServerErrorIO hs -> Proxy qr -> IO () Source #
Run a query-only Mu graphQLApp
on the given port.
runGraphQLAppTrans :: GraphQLApp p qr mut sub m chn hs => Port -> (forall a. m a -> ServerErrorIO a) -> ServerT chn Field p m hs -> Proxy qr -> Proxy mut -> Proxy sub -> IO () Source #
Run a Mu graphQLApp
on a transformer stack on the given port.
Build a WAI Application
graphQLApp :: GraphQLApp p qr mut sub ServerErrorIO chn hs => ServerT chn Field p ServerErrorIO hs -> Proxy qr -> Proxy mut -> Proxy sub -> Application Source #
Turn a Mu GraphQL Server
into a WAI Application
.
Use this version when your server has not only
queries, but also mutations or subscriptions.
graphQLAppQuery :: forall qr p chn hs. GraphQLApp p ('Just qr) 'Nothing 'Nothing ServerErrorIO chn hs => ServerT chn Field p ServerErrorIO hs -> Proxy qr -> Application Source #
Turn a Mu GraphQL Server
into a WAI Application
.
Use this version when your server has only queries.
graphQLAppTrans :: GraphQLApp p qr mut sub m chn hs => (forall a. m a -> ServerErrorIO a) -> ServerT chn Field p m hs -> Proxy qr -> Proxy mut -> Proxy sub -> Application Source #
Turn a Mu GraphQL Server
into a WAI Application
using a combined transformer stack.
See also documentation for graphQLApp
.
graphQLAppTransQuery :: forall qr m p chn hs. GraphQLApp p ('Just qr) 'Nothing 'Nothing m chn hs => (forall a. m a -> ServerErrorIO a) -> ServerT chn Field p m hs -> Proxy qr -> Application Source #
Turn a Mu GraphQL Server
into a WAI Application
using a combined transformer stack.
See also documentation for graphQLAppQuery
.
Lifting of Conduit
s
liftServerConduit :: MonadIO m => ConduitT i o ServerErrorIO r -> ConduitT i o m r Source #
Turns a Conduit
working on ServerErrorIO
into any other base monad which supports IO
,
by raising any error as an exception.
This function is useful to interoperate with
libraries which generate Conduit
s with other
base monads, such as persistent
.