wai-logger-2.2.6: A logging system for WAI

Safe HaskellNone
LanguageHaskell2010

Network.Wai.Logger

Contents

Description

Apache style logger for WAI applications.

An example:

{-# LANGUAGE OverloadedStrings #-}
module Main where

import Blaze.ByteString.Builder (fromByteString)
import Control.Monad.IO.Class (liftIO)
import qualified Data.ByteString.Char8 as BS
import Network.HTTP.Types (status200)
import Network.Wai (Application, responseBuilder)
import Network.Wai.Handler.Warp (run)
import Network.Wai.Logger (withStdoutLogger, ApacheLogger)

main :: IO ()
main = withStdoutLogger $ \aplogger ->
    run 3000 $ logApp aplogger

logApp :: ApacheLogger -> Application
logApp aplogger req response = do
    liftIO $ aplogger req status (Just len)
    response $ responseBuilder status hdr msg
  where
    status = status200
    hdr = [("Content-Type", "text/plain")]
    pong = "PONG"
    msg = fromByteString pong
    len = fromIntegral $ BS.length pong

Synopsis

High level functions

type ApacheLogger = Request -> Status -> Maybe Integer -> IO () Source

Apache style logger.

withStdoutLogger :: (ApacheLogger -> IO a) -> IO a Source

Executing a function which takes ApacheLogger. This ApacheLogger writes log message to stdout. Each buffer (4K bytes) is flushed every second.

Creating a logger

data ApacheLoggerActions Source

Constructors

ApacheLoggerActions 

Fields

apacheLogger :: ApacheLogger
 
logRotator :: IO ()

This is obsoleted. Rotation is done on-demand. So, this is now an empty action.

logRemover :: IO ()

Removing resources relating Apache logger. E.g. flushing and deallocating internal buffers.

Types

data IPAddrSource Source

Source from which the IP source address of the client is obtained.

Constructors

FromSocket

From the peer address of the HTTP connection.

FromHeader

From X-Real-IP: or X-Forwarded-For: in the HTTP header.

FromFallback

From the peer address if header is not found.

data LogType :: *

Logger Type.

Constructors

LogNone

No logging.

LogStdout BufSize

Logging to stdout. BufSize is a buffer size

LogStderr BufSize

Logging to stdout. BufSize is a buffer size for each capability.

LogFileNoRotate FilePath BufSize

Logging to a file. BufSize is a buffer size for each capability.

LogFile FileLogSpec BufSize

Logging to a file. BufSize is a buffer size for each capability. File rotation is done on-demand.

LogCallback (LogStr -> IO ()) (IO ())

Logging with a log and flush action. run flush after log each message.

data FileLogSpec :: *

The spec for logging files

Utilities

showSockAddr :: SockAddr -> NumericAddress Source

Convert SockAddr to NumericAddress. If the address is IPv4-embedded IPv6 address, the IPv4 is extracted.

Backward compability