mig-0.2.1.0: Build lightweight and composable servers
Safe HaskellSafe-Inferred
LanguageGHC2021

Mig.Core.Class.Plugin

Description

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

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.

Instances

Instances details
MonadIO m => ToPlugin (Plugin m) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

MonadIO m => ToPlugin (PluginFun m) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

ToPlugin a => ToPlugin (RawResponse -> a) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

(FromReqBody ty a, ToSchema a, ToPlugin b) => ToPlugin (Body ty a -> b) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

Methods

toPluginInfo :: RouteInfo -> RouteInfo Source #

toPluginFun :: (Body ty a -> b) -> ServerFun (MonadOf (Body ty a -> b)) -> ServerFun (MonadOf (Body ty a -> b)) Source #

(FromHttpApiData a, ToParamSchema a, ToPlugin b, KnownSymbol sym) => ToPlugin (Capture sym a -> b) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

Methods

toPluginInfo :: RouteInfo -> RouteInfo Source #

toPluginFun :: (Capture sym a -> b) -> ServerFun (MonadOf (Capture sym a -> b)) -> ServerFun (MonadOf (Capture sym a -> b)) Source #

(FromForm a, ToPlugin b) => ToPlugin (Cookie a -> b) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

ToPlugin a => ToPlugin (FullPathInfo -> a) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

(FromHttpApiData a, ToParamSchema a, ToPlugin b, KnownSymbol sym) => ToPlugin (Header sym a -> b) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

Methods

toPluginInfo :: RouteInfo -> RouteInfo Source #

toPluginFun :: (Header sym a -> b) -> ServerFun (MonadOf (Header sym a -> b)) -> ServerFun (MonadOf (Header sym a -> b)) Source #

ToPlugin a => ToPlugin (IsSecure -> a) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

(FromHttpApiData a, ToParamSchema a, ToPlugin b, KnownSymbol sym) => ToPlugin (Optional sym a -> b) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

Methods

toPluginInfo :: RouteInfo -> RouteInfo Source #

toPluginFun :: (Optional sym a -> b) -> ServerFun (MonadOf (Optional sym a -> b)) -> ServerFun (MonadOf (Optional sym a -> b)) Source #

(FromHttpApiData a, ToParamSchema a, ToPlugin b, KnownSymbol sym) => ToPlugin (OptionalHeader sym a -> b) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

ToPlugin a => ToPlugin (PathInfo -> a) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

(FromHttpApiData a, ToParamSchema a, ToPlugin b, KnownSymbol sym) => ToPlugin (Query sym a -> b) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

Methods

toPluginInfo :: RouteInfo -> RouteInfo Source #

toPluginFun :: (Query sym a -> b) -> ServerFun (MonadOf (Query sym a -> b)) -> ServerFun (MonadOf (Query sym a -> b)) Source #

(ToPlugin b, KnownSymbol sym) => ToPlugin (QueryFlag sym -> b) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

ToPlugin a => ToPlugin (RawRequest -> a) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

data Plugin m Source #

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 (.).

Constructors

Plugin 

Fields

Instances

Instances details
Monoid (Plugin m) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

Methods

mempty :: Plugin m #

mappend :: Plugin m -> Plugin m -> Plugin m #

mconcat :: [Plugin m] -> Plugin m #

Semigroup (Plugin m) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

Methods

(<>) :: Plugin m -> Plugin m -> Plugin m #

sconcat :: NonEmpty (Plugin m) -> Plugin m #

stimes :: Integral b => b -> Plugin m -> Plugin m #

MonadIO m => ToPlugin (Plugin m) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

type PluginFun m = ServerFun m -> ServerFun m Source #

Low-level plugin function.

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

Constructors

RawResponse (Maybe Response) 

Instances

Instances details
ToPlugin a => ToPlugin (RawResponse -> a) Source # 
Instance details

Defined in Mig.Core.Class.Plugin

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)

processNoResponse :: forall m a. (MonadIO m, IsResp a) => m a -> Plugin m Source #

Sets default response if server response with Nothing. If it can not handle the request.