Copyright | (C) 2024 Bellroy Pty Ltd |
---|---|
License | BSD-3-Clause |
Maintainer | Bellroy Tech Team <haskell@bellroy.com> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
UnliftIO.Servant.Server
Description
The functions in this module make it easier to serve a Servant API,
when its API endpoints are implemented in a monad that has an
MonadUnliftIO
instance. Many monad transformers are morally just
ReaderT
or IdentityT
over some kind of base monad, and these
monads can be unlifted.
This isn't magic—you'll still have to unwrap the outer transformers
to get at the returned Application
—but for simpler application
monads it frees you from fiddling around with rank-2 functions just
to serve your API.
Example use:
import Network.Wai.Handler.Warp (runEnv) -- Some kind of Servant API type MyApi = ... :<|> ... :<|> ... -- API implemented in terms of some application monad, which has aMonadUnliftIO
instance. myApi :: ServerT MyApi SomeApplicationMonad myApi = undefined -- details unimportant main :: IO () main = runSomeApplicationMonad $ do app <-serve
myApi liftIO $ runEnv 3000 app
Synopsis
- serve :: (MonadUnliftIO m, HasServer api '[]) => Proxy api -> ServerT api m -> m Application
- serveExceptT :: (MonadUnliftIO m, HasServer api '[]) => Proxy api -> (e -> ServerError) -> ServerT api (ExceptT e m) -> m Application
- serveWithContext :: (HasServer api context, ServerContext context, MonadUnliftIO m) => Proxy api -> Context context -> ServerT api m -> m Application
- serveExceptTWithContext :: (HasServer api context, ServerContext context, MonadUnliftIO m) => Proxy api -> (e -> ServerError) -> Context context -> ServerT api (ExceptT e m) -> m Application
- genericServe :: (GenericServant routes (AsServerT m), GenericServant routes AsApi, HasServer (ToServantApi routes) '[], ServerT (ToServantApi routes) m ~ ToServant routes (AsServerT m), MonadUnliftIO m) => routes (AsServerT m) -> m Application
- genericServeExceptT :: (GenericServant routes (AsServerT (ExceptT e m)), GenericServant routes AsApi, HasServer (ToServantApi routes) '[], ServerT (ToServantApi routes) (ExceptT e m) ~ ToServant routes (AsServerT (ExceptT e m)), MonadUnliftIO m) => (e -> ServerError) -> routes (AsServerT (ExceptT e m)) -> m Application
- genericServeWithContext :: (GenericServant routes (AsServerT m), GenericServant routes AsApi, HasServer (ToServantApi routes) context, ServerContext context, ServerT (ToServantApi routes) m ~ ToServant routes (AsServerT m), MonadUnliftIO m) => routes (AsServerT m) -> Context context -> m Application
- genericServeExceptTWithContext :: (GenericServant routes (AsServerT (ExceptT e m)), GenericServant routes AsApi, HasServer (ToServantApi routes) context, ServerContext context, ServerT (ToServantApi routes) (ExceptT e m) ~ ToServant routes (AsServerT (ExceptT e m)), MonadUnliftIO m) => (e -> ServerError) -> routes (AsServerT (ExceptT e m)) -> Context context -> m Application
Helpers for traditional-style APIs
serve :: (MonadUnliftIO m, HasServer api '[]) => Proxy api -> ServerT api m -> m Application Source #
Convert a Servant API into an Application
, by unlifting the
monad in which it runs.
serveExceptT :: (MonadUnliftIO m, HasServer api '[]) => Proxy api -> (e -> ServerError) -> ServerT api (ExceptT e m) -> m Application Source #
Convert a Servant API which uses ExceptT
above an unliftable
monad, by converting its errors into Servant's
ServerError
and returning them to the API caller.
serveWithContext :: (HasServer api context, ServerContext context, MonadUnliftIO m) => Proxy api -> Context context -> ServerT api m -> m Application Source #
serveExceptTWithContext :: (HasServer api context, ServerContext context, MonadUnliftIO m) => Proxy api -> (e -> ServerError) -> Context context -> ServerT api (ExceptT e m) -> m Application Source #
As serveExceptT
, with an additional Context
parameter.
Helpers for Generic/records-based APIs
genericServe :: (GenericServant routes (AsServerT m), GenericServant routes AsApi, HasServer (ToServantApi routes) '[], ServerT (ToServantApi routes) m ~ ToServant routes (AsServerT m), MonadUnliftIO m) => routes (AsServerT m) -> m Application Source #
As serve
, but for Servant's generic records.
See: Servant.API.Generic
genericServeExceptT :: (GenericServant routes (AsServerT (ExceptT e m)), GenericServant routes AsApi, HasServer (ToServantApi routes) '[], ServerT (ToServantApi routes) (ExceptT e m) ~ ToServant routes (AsServerT (ExceptT e m)), MonadUnliftIO m) => (e -> ServerError) -> routes (AsServerT (ExceptT e m)) -> m Application Source #
As genericServe
, but for when you have an ExceptT
above the
unliftable monad. As with serveExceptT
, errors are returned to
the API caller.
genericServeWithContext :: (GenericServant routes (AsServerT m), GenericServant routes AsApi, HasServer (ToServantApi routes) context, ServerContext context, ServerT (ToServantApi routes) m ~ ToServant routes (AsServerT m), MonadUnliftIO m) => routes (AsServerT m) -> Context context -> m Application Source #
As genericServe
, but with an additional Context
parameter.
genericServeExceptTWithContext :: (GenericServant routes (AsServerT (ExceptT e m)), GenericServant routes AsApi, HasServer (ToServantApi routes) context, ServerContext context, ServerT (ToServantApi routes) (ExceptT e m) ~ ToServant routes (AsServerT (ExceptT e m)), MonadUnliftIO m) => (e -> ServerError) -> routes (AsServerT (ExceptT e m)) -> Context context -> m Application Source #
As genericServeExceptT
, but with an additional Context
parameter.