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 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
- type ApacheLogger = Request -> Status -> Maybe Integer -> IO ()
- withStdoutLogger :: (ApacheLogger -> IO a) -> IO a
- type ServerPushLogger = Request -> ByteString -> Integer -> IO ()
- data ApacheLoggerActions
- apacheLogger :: ApacheLoggerActions -> ApacheLogger
- serverpushLogger :: ApacheLoggerActions -> ServerPushLogger
- logRotator :: ApacheLoggerActions -> IO ()
- logRemover :: ApacheLoggerActions -> IO ()
- initLogger :: IPAddrSource -> LogType -> IO FormattedTime -> IO ApacheLoggerActions
- data IPAddrSource
- data LogType :: *
- = LogNone
- | LogStdout BufSize
- | LogStderr BufSize
- | LogFileNoRotate FilePath BufSize
- | LogFile FileLogSpec BufSize
- | LogCallback (LogStr -> IO ()) (IO ())
- data FileLogSpec :: * = FileLogSpec {}
- showSockAddr :: SockAddr -> NumericAddress
- logCheck :: LogType -> IO ()
- clockDateCacher :: IO (DateCacheGetter, DateCacheUpdater)
- type ZonedDate = FormattedTime
- type DateCacheGetter = IO ZonedDate
- type DateCacheUpdater = IO ()
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.
type ServerPushLogger = Request -> ByteString -> Integer -> IO () Source #
HTTP/2 server push logger in Apache style.
Creating a logger
data ApacheLoggerActions Source #
Function set of Apache style logger.
apacheLogger :: ApacheLoggerActions -> ApacheLogger Source #
The Apache logger.
serverpushLogger :: ApacheLoggerActions -> ServerPushLogger Source #
The HTTP/2 server push logger.
logRotator :: ApacheLoggerActions -> IO () Source #
This is obsoleted. Rotation is done on-demand. So, this is now an empty action.
logRemover :: ApacheLoggerActions -> IO () Source #
Removing resources relating to Apache logger. E.g. flushing and deallocating internal buffers.
initLogger :: IPAddrSource -> LogType -> IO FormattedTime -> 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.
LogNone | No logging. |
LogStdout BufSize | Logging to stdout.
|
LogStderr BufSize | Logging to stdout.
|
LogFileNoRotate FilePath BufSize | Logging to a file.
|
LogFile FileLogSpec BufSize | Logging to a file.
|
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
clockDateCacher :: IO (DateCacheGetter, DateCacheUpdater) Source #
Returning DateCacheGetter
and DateCacheUpdater
.
Note: Since version 2.1.2, this function uses the auto-update package
internally, and therefore the DateCacheUpdater
value returned need
not be called. To wit, the return value is in fact an empty action.
type ZonedDate = FormattedTime Source #
A type for zoned date.
type DateCacheUpdater = IO () Source #
Updateing cached ZonedDate
. This should be called every second.
See the source code of withStdoutLogger
.