Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 :: KatipContext m => Severity -> MiddlewareT m
- middlewareCustom :: MonadIO m => Options m -> MiddlewareT m
- type ApplicationT (m :: Type -> Type) = Request -> (Response -> m ResponseReceived) -> m ResponseReceived
- type MiddlewareT (m :: Type -> Type) = ApplicationT m -> ApplicationT m
- runApplication :: MonadIO m => (forall a. m a -> IO a) -> ApplicationT m -> Application
- data Options (m :: Type -> Type) = Options {
- handleRequest :: forall a. Request -> m a -> m a
- handleResponse :: forall a. Response -> m a -> m a
- addRequestAndResponseToContext :: forall (m :: Type -> Type). KatipContext m => Formatter Request -> Formatter Response -> Options m
- logRequestAndResponse :: forall (m :: Type -> Type). KatipContext m => Severity -> Options m
- options :: forall (m :: Type -> Type). KatipContext m => Formatter Request -> Formatter Response -> Severity -> Options m
- defaultOptions :: forall (m :: Type -> Type). KatipContext m => Severity -> Options m
- type Formatter a = a -> Value
- data TimeUnit
- type IncludedHeaders = Set HeaderName
- defaultIncludedHeaders :: IncludedHeaders
- defaultRequestFormat :: IncludedHeaders -> Formatter Request
- defaultResponseFormat :: IncludedHeaders -> TimeUnit -> Formatter Response
- data Request = Request {}
- traceRequest :: MonadIO m => Request -> m Request
- data Response = Response {}
- traceResponse :: MonadIO m => Request -> Response -> m Response
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 ]
Options | |
|
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.
defaultOptions :: forall (m :: Type -> Type). KatipContext m => Severity -> Options m Source #
Same as options
, but uses defaultRequestFormat
,defaultResponseFormat
, and Milliseconds
.
Formatting
Unit of time to use when logging response times.
Instances
Bounded TimeUnit Source # | |
Enum TimeUnit Source # | |
Show TimeUnit Source # | |
Eq TimeUnit Source # | |
Ord TimeUnit Source # | |
Defined in Katip.Wai.Options |
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 Request
s.
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" }
Request
An incoming http request.
Request | |
|
Response
Response that was sent back to client.
Response | |
|