module System.FastLogger
( Logger
, timestampedLogEntry
, combinedLogEntry
, newLogger
, newLoggerWithCustomErrorFunction
, logMsg
, stopLogger
) where
import Blaze.ByteString.Builder
import Blaze.ByteString.Builder.Char.Utf8
import Control.Concurrent
import Control.Concurrent.Extended (forkIOLabeledWithUnmaskBs)
import Control.Exception
import Control.Monad
import Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.Char8 as S
import Data.ByteString.Internal (c2w)
import qualified Data.ByteString.Lazy.Char8 as L
import Data.Int
import Data.IORef
import Data.Monoid
import qualified Data.Text as T
import qualified Data.Text.Encoding as T
#if !MIN_VERSION_base(4,6,0)
import Prelude hiding (catch)
#endif
import System.IO
import Snap.Internal.Http.Server.Date
data Logger = Logger
{ _queuedMessages :: !(IORef Builder)
, _dataWaiting :: !(MVar ())
, _loggerPath :: !(FilePath)
, _loggingThread :: !(MVar ThreadId)
, _errAction :: ByteString -> IO ()
}
newLogger :: FilePath
-> IO Logger
newLogger = newLoggerWithCustomErrorFunction
(\s -> S.hPutStr stderr s >> hFlush stderr)
newLoggerWithCustomErrorFunction :: (ByteString -> IO ())
-> FilePath
-> IO Logger
newLoggerWithCustomErrorFunction errAction fp = do
q <- newIORef mempty
dw <- newEmptyMVar
th <- newEmptyMVar
let lg = Logger q dw fp th errAction
mask_ $ do
tid <- forkIOLabeledWithUnmaskBs "snap-server: logging" $
loggingThread lg
putMVar th tid
return lg
timestampedLogEntry :: ByteString -> IO ByteString
timestampedLogEntry msg = do
timeStr <- getLogDateString
return $! toByteString
$! mconcat [ fromWord8 $ c2w '['
, fromByteString timeStr
, fromByteString "] "
, fromByteString msg ]
combinedLogEntry :: ByteString
-> Maybe ByteString
-> ByteString
-> Int
-> Maybe Int64
-> Maybe ByteString
-> ByteString
-> IO ByteString
combinedLogEntry !host !mbUser !req !status !mbNumBytes !mbReferer !ua = do
timeStr <- getLogDateString
let !l = [ fromByteString host
, fromByteString " - "
, user
, fromByteString " ["
, fromByteString timeStr
, fromByteString "] \""
, fromByteString req
, fromByteString "\" "
, fromShow status
, space
, numBytes
, space
, referer
, fromByteString " \""
, fromByteString ua
, quote ]
let !output = toByteString $ mconcat l
return $! output
where
dash = fromWord8 $ c2w '-'
quote = fromWord8 $ c2w '\"'
space = fromWord8 $ c2w ' '
user = maybe dash fromByteString mbUser
numBytes = maybe dash fromShow mbNumBytes
referer = maybe dash
(\s -> mconcat [ quote
, fromByteString s
, quote ])
mbReferer
logMsg :: Logger -> ByteString -> IO ()
logMsg !lg !s = do
let !s' = fromByteString s `mappend` (fromWord8 $ c2w '\n')
atomicModifyIORef (_queuedMessages lg) $ \d -> (d `mappend` s',())
tryPutMVar (_dataWaiting lg) () >> return ()
loggingThread :: Logger -> (forall a. IO a -> IO a) -> IO ()
loggingThread (Logger queue notifier filePath _ errAct) unmask = do
initialize >>= go
where
openIt =
if filePath == "-"
then return stdout
else
if filePath == "stderr"
then return stderr
else openFile filePath AppendMode `catch`
\(e::IOException) -> do
logInternalError $ "Can't open log file \"" ++
filePath ++ "\".\n"
logInternalError $ "Exception: " ++ show e ++ "\n"
logInternalError $ "Logging to stderr instead. " ++
"**THIS IS BAD, YOU OUGHT TO " ++
"FIX THIS**\n\n"
return stderr
closeIt h = unless (h == stdout || h == stderr) $
hClose h
logInternalError = errAct . T.encodeUtf8 . T.pack
go (href, lastOpened) =
(unmask $ forever $ waitFlushDelay (href, lastOpened))
`catches`
[ Handler $ \(_::AsyncException) -> killit (href, lastOpened)
, Handler $ \(e::SomeException) -> do
logInternalError $ "logger got exception: "
++ Prelude.show e ++ "\n"
threadDelay 20000000
go (href, lastOpened) ]
initialize = do
lh <- openIt
href <- newIORef lh
t <- getCurrentDateTime
tref <- newIORef t
return (href, tref)
killit (href, lastOpened) = do
flushIt (href, lastOpened)
h <- readIORef href
closeIt h
flushIt (!href, !lastOpened) = do
dl <- atomicModifyIORef queue $ \x -> (mempty,x)
let !msgs = toLazyByteString dl
h <- readIORef href
(do L.hPut h msgs
hFlush h) `catch` \(e::IOException) -> do
logInternalError $ "got exception writing to log " ++
filePath ++ ": " ++ show e ++ "\n"
logInternalError $ "writing log entries to stderr.\n"
mapM_ errAct $ L.toChunks msgs
t <- getCurrentDateTime
old <- readIORef lastOpened
when (told > 900) $ do
closeIt h
mask_ $ openIt >>= writeIORef href
writeIORef lastOpened t
waitFlushDelay !d = do
_ <- takeMVar notifier
flushIt d
threadDelay 5000000
stopLogger :: Logger -> IO ()
stopLogger lg = withMVar (_loggingThread lg) killThread