Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Plugins are useful to apply certain action to all routes in the server. For example we can add generic logger or authorization bazed on common query parameter or field of the body request that contains token of the session.
The downside is that we work on low level of Requesnce/Response as we have rendered all routes to ServerFun. But thw good part of it is that we can add generic action to every route.
Let's consider a simple example of adding logger to lall routes:
logRoutes :: Server IO -> Server IO logRoutes = applyPlugin $ \(PathInfo path) -> prependServerAction $ when (path /= ["favicon.ico"] && headMay path /= Just "static") $ do logRoute site (Text.intercalate "/" path) -- | Logs the route info logRoute :: Site -> Text -> IO () logRoute site route = do time <- getCurrentTime site.logInfo $ route <> " page visited at: " <> Text.pack (show time)
Here we use instance of ToPlugin for PathInfo
to read full path for any route
and we use this information in the logger.
We have various instances for everything that we can query from the request and we can use this information to transform the server functions inside the routes.
The instances work in the same manner as route handlers we can use as many arguments as we wish and we use typed wrappers to query specific part of the request. Thus we gain type-safety and get convenient interface to request the various parts of request.
Synopsis
- class MonadIO (MonadOf f) => ToPlugin f where
- toPluginInfo :: RouteInfo -> RouteInfo
- toPluginFun :: f -> ServerFun (MonadOf f) -> ServerFun (MonadOf f)
- data Plugin m = Plugin {}
- type PluginFun m = ServerFun m -> ServerFun m
- toPlugin :: forall f. ToPlugin f => f -> Plugin (MonadOf f)
- fromPluginFun :: MonadIO m => PluginFun m -> Plugin m
- ($:) :: forall f. ToPlugin f => f -> Server (MonadOf f) -> Server (MonadOf f)
- applyPlugin :: forall f. ToPlugin f => f -> Server (MonadOf f) -> Server (MonadOf f)
- newtype RawResponse = RawResponse (Maybe Response)
- prependServerAction :: forall m. MonadIO m => m () -> Plugin m
- appendServerAction :: forall m. MonadIO m => m () -> Plugin m
- processResponse :: forall m. MonadIO m => (m (Maybe Response) -> m (Maybe Response)) -> Plugin m
- whenSecure :: forall m. MonadIO m => Plugin m
- processNoResponse :: forall m a. (MonadIO m, IsResp a) => m a -> Plugin m
class
class MonadIO (MonadOf f) => ToPlugin f where Source #
Values that can represent a plugin. We use various newtype-wrappers to query type-safe info from request.
toPluginInfo :: RouteInfo -> RouteInfo Source #
toPluginFun :: f -> ServerFun (MonadOf f) -> ServerFun (MonadOf f) Source #
Instances
Plugin can convert all routes of the server.
It is wrapper on top of ServerFun m -> ServerFun m
.
We can apply plugins to servers with applyPlugin
function
also plugin has Monoid instance which is like Monoid.Endo or functional composition (.)
.
toPlugin :: forall f. ToPlugin f => f -> Plugin (MonadOf f) Source #
Convert plugin-like value to plugin.
($:) :: forall f. ToPlugin f => f -> Server (MonadOf f) -> Server (MonadOf f) Source #
Infix operator for applyPlugin
applyPlugin :: forall f. ToPlugin f => f -> Server (MonadOf f) -> Server (MonadOf f) Source #
Applies plugin to all routes of the server.
newtype RawResponse Source #
Read low-level response. Note that it does not affect the API schema
Instances
ToPlugin a => ToPlugin (RawResponse -> a) Source # | |
Defined in Mig.Core.Class.Plugin toPluginInfo :: RouteInfo -> RouteInfo Source # toPluginFun :: (RawResponse -> a) -> ServerFun (MonadOf (RawResponse -> a)) -> ServerFun (MonadOf (RawResponse -> a)) Source # |
specific plugins
prependServerAction :: forall m. MonadIO m => m () -> Plugin m Source #
Prepends action to the server
appendServerAction :: forall m. MonadIO m => m () -> Plugin m Source #
Post appends action to the server
processResponse :: forall m. MonadIO m => (m (Maybe Response) -> m (Maybe Response)) -> Plugin m Source #
Applies transformation to the response
whenSecure :: forall m. MonadIO m => Plugin m Source #
Execute request only if it is secure (made with SSL connection)