katip-wai-0.2.0.0: WAI middleware for logging request and response info through katip.
Safe HaskellNone
LanguageHaskell2010

Katip.Wai

Description

Add information about the Request, Response, and the response time to Katip's LogContexts.

Example setup:

import Control.Exception (bracket)
import Data.Proxy (Proxy (Proxy))
import Katip qualified
import Katip.Wai (ApplicationT, runApplication)
import Katip.Wai qualified
import Network.Wai.Handler.Warp qualified as Warp
import Servant qualified
import System.IO (stdout)
import UnliftIO (MonadUnliftIO (withRunInIO))


type Api = Servant.GetNoContent


server :: Servant.ServerT Api (Katip.KatipContextT Servant.Handler)
server = do
  Katip.logLocM Katip.InfoS "This message should also have the request context"
  pure Servant.NoContent


mkApplication :: ApplicationT (Katip.KatipContextT IO)
mkApplication = Katip.Wai.middleware Katip.InfoS $ request send -> do
  logEnv <- Katip.getLogEnv
  context <- Katip.getKatipContext
  namespace <- Katip.getKatipNamespace

  let hoistedApp =
        let proxy = Proxy @Api
            hoistedServer = Servant.hoistServer proxy (Katip.runKatipContextT logEnv context namespace) server
         in Servant.serve proxy hoistedServer

  withRunInIO $ toIO -> hoistedApp request (toIO . send)


withLogEnv :: (Katip.LogEnv -> IO a) -> IO a
withLogEnv useLogEnv = do
  handleScribe <-
    Katip.mkHandleScribeWithFormatter
      Katip.jsonFormat
      (Katip.ColorLog False)
      stdout
      (Katip.permitItem minBound)
      Katip.V3

  let makeLogEnv =
        Katip.initLogEnv "example-app" "local-dev"
          >>= Katip.registerScribe "stdout" handleScribe Katip.defaultScribeSettings

  bracket makeLogEnv Katip.closeScribes useLogEnv


main :: IO ()
main = withLogEnv $ logEnv ->
  let
    app = runApplication (Katip.runKatipContextT logEnv () "main") mkApplication
   in
    Warp.run 5555 app

Example output:

{"app":["example-app"],"at":"2024-09-07T18:44:10.411097829Z","data":{"request":{"headers":{Host:"localhost:5555","User-Agent":"curl8.9.1"},"httpVersion":"HTTP1.1","id":"7ec0fbc4-722c-4c70-a168-c2abe5c7b4fa","isSecure":false,"method":GET,"path":"/","queryString":[],"receivedAt":"2024-09-07T18:44:10.411057334Z","remoteHost":"127.0.0.1:51230"}},"env":"local-dev","host":"x1g11","loc":null,"msg":"Request received.","ns":["example-app","main"],"pid":"106249","sev":Info,"thread":"27"}
{"app":["example-app"],"at":"2024-09-07T18:44:10.411097829Z","data":{"request":{"headers":{Host:"localhost:5555","User-Agent":"curl8.9.1"},"httpVersion":"HTTP1.1","id":"7ec0fbc4-722c-4c70-a168-c2abe5c7b4fa","isSecure":false,"method":GET,"path":"","queryString":[],"receivedAt":"2024-09-07T18:44:10.411057334Z","remoteHost":"127.0.0.1:51230"}},"env":"local-dev","host":"x1g11","loc":{"loc_col":3,"loc_fn":"srcKatipWaiExample/Short.hs","loc_ln":19,"loc_mod":Katip.Wai.Example.Short,"loc_pkg":"my-katip-wai-example-0.1.0.0-inplace"},"msg":"This message should also have the request context","ns":["example-app","main"],"pid":"106249","sev":Info,"thread":"27"}
{"app":["example-app"],"at":"2024-09-07T18:44:10.411097829Z","data":{"request":{"headers":{Host:"localhost:5555","User-Agent":"curl8.9.1"},"httpVersion":"HTTP1.1","id":"7ec0fbc4-722c-4c70-a168-c2abe5c7b4fa","isSecure":false,"method":GET,"path":"/","queryString":[],"receivedAt":"2024-09-07T18:44:10.411057334Z","remoteHost":"127.0.0.1:51230"},"response":{"headers":{},"respondedAt":"2024-09-07T18:44:10.411199014Z","responseTime":{"time":0.137369,"unit":"ms"},"status":{"code":204,"message":"No Content"}}},"env":"local-dev","host":"x1g11","loc":null,"msg":"Response sent.","ns":["example-app","main"],"pid":"106249","sev":Info,"thread":"27"}
Synopsis

Middleware

Middleware for logging request and response information.

middleware :: KatipContext m => Severity -> MiddlewareT m Source #

Add the request and response to the LogContexts, and log a message when a request is received and when a response is sent.

This uses the default format: defaultRequestFormat and defaultResponseFormat with milliseconds for the response time.

If you want more customization see middlewareCustom.

middlewareCustom :: MonadIO m => Options m -> MiddlewareT m Source #

Same as middleware, but allows you to customize how the Request and Response are handled.

Helpers

Since logging with Katip is monadic, we need the ability to run an Application or Middleware in a monad other than IO.

type ApplicationT (m :: Type -> Type) = Request -> (Response -> m ResponseReceived) -> m ResponseReceived Source #

Just like Application except it runs in m instead of IO

type MiddlewareT (m :: Type -> Type) = ApplicationT m -> ApplicationT m Source #

Just like Middleware except it runs in m instead of IO

runApplication :: MonadIO m => (forall a. m a -> IO a) -> ApplicationT m -> Application Source #

Converts an ApplicationT to a normal Application

Options

Options for customizing the way middlewareCustom handles the requests and responses.

data Options (m :: Type -> Type) Source #

Options to customize how to handle the Request and Response.

You can use Monoid to combine Options:

mconcat
  [ addRequestAndResponseToContext
      requestFormatter
      responseFormatter
  , logRequestAndResponse severity
  ]

Constructors

Options 

Fields

Instances

Instances details
Monoid (Options m) Source # 
Instance details

Defined in Katip.Wai.Options

Methods

mempty :: Options m #

mappend :: Options m -> Options m -> Options m #

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

Semigroup (Options m) Source # 
Instance details

Defined in Katip.Wai.Options

Methods

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

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

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

addRequestAndResponseToContext :: forall (m :: Type -> Type). KatipContext m => Formatter Request -> Formatter Response -> Options m Source #

Add the Request to the LogContexts under "request", and add Response to the LogContext under "response".

logRequestAndResponse :: forall (m :: Type -> Type). KatipContext m => Severity -> Options m Source #

Log "Request received." when a request comes in, and log "Response sent." when a response is sent back.

options :: forall (m :: Type -> Type). KatipContext m => Formatter Request -> Formatter Response -> Severity -> Options m Source #

Combines addRequestAndResponseToContext and logRequestAndResponse with the formatters and severity you provide.

Formatting

Functions for formatting the Requests and Responses.

type Formatter a = a -> Value Source #

A formatter is a function that can convert a into json.

data TimeUnit Source #

Unit of time to use when logging response times.

type IncludedHeaders = Set HeaderName Source #

Headers to include in your logs.

defaultIncludedHeaders :: IncludedHeaders Source #

Default list of headers to include in logs: Host, Referer, 'User-Agent', and Range.

defaultRequestFormat :: IncludedHeaders -> Formatter Request Source #

Default formatter for Requests.

Example:

{
   "headers": {
     Host: "localhost:4000",
     Referer: "http://localhost:4000/docs/",
     "User-Agent": "Mozilla5.0 (X11; Linux x86_64; rv:130.0) Gecko20100101 Firefox/130.0"
   },
   "httpVersion": "HTTP/1.1",
   "id": "299b188e-f695-49ee-a92f-9078a29f2ec4",
   "isSecure": false,
   "method": GET,
   "path": "/openapi.json",
   "queryString": [],
   "receivedAt": "2024-09-07T18:22:50.943042066Z",
   "remoteHost": "127.0.0.1:58046"
 }

defaultResponseFormat :: IncludedHeaders -> TimeUnit -> Formatter Response Source #

Default formatter for Responses.

Example:

{
   "headers": {},
   "respondedAt": "2024-09-07T18:22:50.943213512Z",
   "responseTime": {
     "time": 0.167463,
     "unit": "ms"
   },
   "status": {
     "code": 200,
     "message": OK
   }
 }

Request

data Request Source #

An incoming http request.

Constructors

Request 

Fields

Instances

Instances details
Show Request Source # 
Instance details

Defined in Katip.Wai.Request

Eq Request Source # 
Instance details

Defined in Katip.Wai.Request

Methods

(==) :: Request -> Request -> Bool #

(/=) :: Request -> Request -> Bool #

traceRequest :: MonadIO m => Request -> m Request Source #

Trace a Request by assigning it a unique UUID and capture information about the request.

Response

data Response Source #

Response that was sent back to client.

Constructors

Response 

Fields

Instances

Instances details
Show Response Source # 
Instance details

Defined in Katip.Wai.Response

Eq Response Source # 
Instance details

Defined in Katip.Wai.Response

traceResponse :: MonadIO m => Request -> Response -> m Response Source #

Trace a response and time how long it took to process a request.