Safe Haskell | None |
---|---|
Language | Haskell2010 |
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
- type ApacheLogger = Request -> Status -> Maybe Integer -> IO ()
- withStdoutLogger :: (ApacheLogger -> IO a) -> IO a
- data ApacheLoggerActions = ApacheLoggerActions {
- apacheLogger :: ApacheLogger
- logFlusher :: IO ()
- logRotator :: IO ()
- logRemover :: IO ()
- initLogger :: IPAddrSource -> LogType -> DateCacheGetter -> IO ApacheLoggerActions
- data IPAddrSource
- data LogType
- = LogNone
- | LogStdout BufSize
- | LogFile FileLogSpec BufSize
- | LogCallback (LogStr -> IO ()) (IO ())
- data FileLogSpec :: * = FileLogSpec {}
- clockDateCacher :: IO (DateCacheGetter, DateCacheUpdater)
- type ZonedDate = ByteString
- type DateCacheGetter = IO ZonedDate
- type DateCacheUpdater = IO ()
- logCheck :: LogType -> IO ()
- showSockAddr :: SockAddr -> NumericAddress
High level functions
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
ApacheLoggerActions | |
|
initLogger :: IPAddrSource -> LogType -> DateCacheGetter -> IO ApacheLoggerActions Source
Creating ApacheLogger
according to LogType
.
Types
data IPAddrSource Source
Source from which the IP source address of the client is obtained.
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. |
Logger Type.
data FileLogSpec :: *
The spec for logging files
Date cacher
clockDateCacher :: IO (DateCacheGetter, DateCacheUpdater) Source
Returning DateCacheGetter
and DateCacheUpdater
.
type ZonedDate = ByteString Source
A type for zoned date.
type DateCacheGetter = IO ZonedDate Source
Getting cached ZonedDate
.
type DateCacheUpdater = IO () Source
Updateing cached ZonedDate
. This should be called every second.
See the source code of withStdoutLogger
.
Utilities
showSockAddr :: SockAddr -> NumericAddress Source
Convert SockAddr
to NumericAddress
. If the address is
IPv4-embedded IPv6 address, the IPv4 is extracted.