Copyright | (c) 2020 Alex Chapman |
---|---|
License | BSD3 |
Maintainer | alex@farfromthere.net |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
A simple usage scenario is that you create your API,
then implement a server for it in a 'ServerT api (Sem (Error ServerError ': r))' monad (where api
is your API type),
then run it with runWarpServer
.
See example/Server.hs for a trivial example of this.
If you need to take your Servant-Polysemy server and run it in an ordinary Servant server then you can use hoistServerIntoSem
.
This can be used to e.g. add Swagger docs to your server, as in example/ServerWithSwagger.hs.
Synopsis
- hoistServerIntoSem :: forall api r. (HasServer api '[], Members '[Error ServerError, Embed IO] r) => Server api -> ServerT api (Sem r)
- liftHandler :: Members '[Error ServerError, Embed IO] r => Handler a -> Sem r a
- serveSem :: forall api r. HasServer api '[] => (forall x. Sem r x -> IO x) -> ServerT api (Sem (Error ServerError ': r)) -> Application
- semHandler :: (forall x. Sem r x -> IO x) -> Sem (Error ServerError ': r) a -> Handler a
- runWarpServer :: forall api r. (HasServer api '[], Member (Embed IO) r) => Port -> Bool -> ServerT api (Sem (Error ServerError ': r)) -> Sem r ()
- runWarpServerSettings :: forall api r. (HasServer api '[], Member (Embed IO) r) => Settings -> ServerT api (Sem (Error ServerError ': r)) -> Sem r ()
- type Redirect (code :: Nat) loc = Verb 'GET code '[JSON] (Headers '[Header "Location" loc] NoContent)
- redirect :: ToHttpApiData a => a -> Sem r (Headers '[Header "Location" a] NoContent)
Use ordinary Servant code in a Polysemy Sem
hoistServerIntoSem :: forall api r. (HasServer api '[], Members '[Error ServerError, Embed IO] r) => Server api -> ServerT api (Sem r) Source #
liftHandler :: Members '[Error ServerError, Embed IO] r => Handler a -> Sem r a Source #
Use Servant-Polysemy code in an ordinary Servant/WAI system
serveSem :: forall api r. HasServer api '[] => (forall x. Sem r x -> IO x) -> ServerT api (Sem (Error ServerError ': r)) -> Application Source #
Turn a ServerT
that contains a Sem
(as returned by hoistServerIntoSem
) into a WAI Application
.
semHandler :: (forall x. Sem r x -> IO x) -> Sem (Error ServerError ': r) a -> Handler a Source #
Turn a Sem
that can throw ServerError
s into a Servant Handler
.
Use Warp to serve a Servant-Polysemy API in a Sem
stack.
:: forall api r. (HasServer api '[], Member (Embed IO) r) | |
=> Port | The port to listen on, e.g. '8080' |
-> Bool | Whether to show exceptions in the http response (good for debugging but potentially a security risk) |
-> ServerT api (Sem (Error ServerError ': r)) | The server to run. You can create one of these with |
-> Sem r () |
Run the given server on the given port, possibly showing exceptions in the responses.
runWarpServerSettings :: forall api r. (HasServer api '[], Member (Embed IO) r) => Settings -> ServerT api (Sem (Error ServerError ': r)) -> Sem r () Source #
Run the given server with these Warp settings.
Redirect paths in a Servant-Polysemy API
type Redirect (code :: Nat) loc = Verb 'GET code '[JSON] (Headers '[Header "Location" loc] NoContent) Source #
A redirect response with the given code, the new location given in the given type, e.g:
> Redirect 302 Text
This will return a '302 Found' response, and we will use Text
in the server to say where it will redirect to.