wai-logger-2.0.2: A logging system for WAI

Safe HaskellNone

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 = do
     liftIO $ aplogger req status (Just len)
     return $ responseBuilder status hdr msg
   where
     status = status200
     hdr = [("Content-Type", "text/plain")
           ,("Content-Length", BS.pack (show len))]
     pong = "PONG"
     len = fromIntegral $ BS.length pong
     msg = toLogStr pong

Synopsis

High level functions

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

Apache style logger.

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

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
 
logFlusher :: IO ()

Flushing log messages in the buffers. This is explicitly called from your program. Probably, one second and 10 seconds is proper to stdout and log files, respectively. See the source code of withStdoutLogger.

logRotator :: IO ()

Rotating log files. This is explicitly called from your program. Probably, 10 seconds is proper.

logRemover :: IO ()

Removing resources relating Apache logger.

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 Source

Logger Type.

Constructors

LogNone

No logging.

LogStdout BufSize

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

LogFile FileLogSpec BufSize

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

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

data FileLogSpec

The spec for logging files

Date cacher

type ZonedDate = ByteStringSource

A type for zoned date.

type DateCacheUpdater = IO ()Source

Updateing cached ZonedDate. This should be called every second. See the source code of withStdoutLogger.

Utilities

logCheck :: LogType -> IO ()Source

Checking if a log file can be written if LogType is LogFile.

showSockAddr :: SockAddr -> NumericAddressSource

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