{-# LANGUAGE OverloadedStrings, TypeSynonymInstances, FlexibleInstances, ExistentialQuantification, TypeFamilies, GeneralizedNewtypeDeriving, StandaloneDeriving, MultiParamTypeClasses, UndecidableInstances #-}
module System.Log.Heavy.Backends
(
FastLoggerBackend,
SyslogBackend,
ChanLoggerBackend,
ParallelBackend,
NullBackend,
Filtering, filtering, excluding,
LogBackendSettings (..),
defStdoutSettings,
defStderrSettings,
defFileSettings,
defaultSyslogSettings,
defaultSyslogFormat
) where
import Control.Monad
import Control.Monad.Trans (liftIO)
import Control.Concurrent
import qualified Data.ByteString.Unsafe as BSU
import qualified Data.Text.Format.Heavy as F
import qualified System.Posix.Syslog as Syslog
import System.Log.FastLogger as FL
import Foreign.C.String (CString, newCString)
import Foreign.Marshal.Alloc (free)
import System.Log.Heavy.Types
import System.Log.Heavy.Level
import System.Log.Heavy.Format
import System.Log.Heavy.Util
defStdoutSettings :: LogBackendSettings FastLoggerBackend
defStdoutSettings = FastLoggerSettings defaultLogFormat (FL.LogStdout FL.defaultBufSize)
defStderrSettings :: LogBackendSettings FastLoggerBackend
defStderrSettings = FastLoggerSettings defaultLogFormat (FL.LogStderr FL.defaultBufSize)
defFileSettings :: FilePath -> LogBackendSettings FastLoggerBackend
defFileSettings path = FastLoggerSettings defaultLogFormat (FL.LogFile spec FL.defaultBufSize)
where spec = FL.FileLogSpec path (10*1024*1024) 3
data FastLoggerBackend = FastLoggerBackend {
flbSettings :: LogBackendSettings FastLoggerBackend,
flbTimedLogger :: TimedFastLogger,
flbCleanup :: IO ()
}
instance IsLogBackend FastLoggerBackend where
data LogBackendSettings FastLoggerBackend = FastLoggerSettings {
lsFormat :: F.Format
, lsType :: FL.LogType
}
initLogBackend settings = do
tcache <- newTimeCache simpleTimeFormat'
(logger, cleanup) <- newTimedFastLogger tcache (lsType settings)
return $ FastLoggerBackend settings logger cleanup
cleanupLogBackend b = do
flbCleanup b
makeLogger backend msg = do
let settings = flbSettings backend
let format = lsFormat settings
let logger = flbTimedLogger backend
logger $ formatLogMessage format msg
defaultSyslogSettings :: LogBackendSettings SyslogBackend
defaultSyslogSettings = SyslogSettings defaultSyslogFormat "application" [] Syslog.User
defaultSyslogFormat :: F.Format
defaultSyslogFormat = "[{level}] {source}: {message}"
data SyslogBackend = SyslogBackend {
sbSettings :: LogBackendSettings SyslogBackend,
sbIdent :: CString,
sbTimeCache :: IO FormattedTime
}
instance IsLogBackend SyslogBackend where
data LogBackendSettings SyslogBackend = SyslogSettings {
ssFormat :: F.Format
, ssIdent :: String
, ssOptions :: [Syslog.Option]
, ssFacility :: Syslog.Facility
}
initLogBackend settings = do
ident <- newCString (ssIdent settings)
tcache <- newTimeCache simpleTimeFormat'
Syslog.openlog ident (ssOptions settings) (ssFacility settings)
return $ SyslogBackend settings ident tcache
cleanupLogBackend backend = do
free $ sbIdent backend
Syslog.closelog
makeLogger backend msg = do
let settings = sbSettings backend
let format = ssFormat settings
facility = ssFacility settings
tcache = sbTimeCache backend
time <- tcache
let str = formatLogMessage format msg time
BSU.unsafeUseAsCStringLen (fromLogStr str) $
Syslog.syslog (Just facility) (levelToPriority $ lmLevel msg)
data ChanLoggerBackend = ChanLoggerBackend {
clChan :: Chan LogMessage
}
instance IsLogBackend ChanLoggerBackend where
data LogBackendSettings ChanLoggerBackend =
ChanLoggerSettings (Chan LogMessage)
initLogBackend (ChanLoggerSettings chan) =
return $ ChanLoggerBackend chan
cleanupLogBackend _ = return ()
makeLogger backend msg = do
liftIO $ writeChan (clChan backend) msg
data ParallelBackend = ParallelBackend ![AnyLogBackend]
instance IsLogBackend ParallelBackend where
data LogBackendSettings ParallelBackend = ParallelLogSettings [LoggingSettings]
wouldWriteMessage (ParallelBackend list) msg = do
results <- sequence [wouldWriteMessage backend msg | backend <- list]
return $ or results
makeLogger (ParallelBackend list) msg =
forM_ list $ \(AnyLogBackend backend) -> makeLogger backend msg
initLogBackend (ParallelLogSettings list) = do
backends <- do
forM list $ \(LoggingSettings settings) -> do
backend <- initLogBackend settings
return $ AnyLogBackend backend
return $ ParallelBackend backends
cleanupLogBackend (ParallelBackend list) =
forM_ (reverse list) $ \(AnyLogBackend backend) -> cleanupLogBackend backend
data Filtering b = FilteringBackend (LogMessage -> Bool) b
filtering :: IsLogBackend b => LogFilter -> LogBackendSettings b -> LogBackendSettings (Filtering b)
filtering fltr b = Filtering (checkLogLevel fltr) b
excluding :: IsLogBackend b => LogFilter -> LogBackendSettings b -> LogBackendSettings (Filtering b)
excluding fltr b = Filtering ex b
where
ex msg = not $ checkContextFilter' [LogContextFilter Nothing (Just fltr)] (lmSource msg) (lmLevel msg)
instance IsLogBackend b => IsLogBackend (Filtering b) where
data LogBackendSettings (Filtering b) = Filtering (LogMessage -> Bool) (LogBackendSettings b)
wouldWriteMessage (FilteringBackend fltr _) msg = do
return $ fltr msg
makeLogger (FilteringBackend fltr backend) msg = do
when (fltr msg) $ do
makeLogger backend msg
initLogBackend (Filtering fltr settings) = do
backend <- initLogBackend settings
return $ FilteringBackend fltr backend
cleanupLogBackend (FilteringBackend _ b) = cleanupLogBackend b
data NullBackend = NullBackend
instance IsLogBackend NullBackend where
data LogBackendSettings NullBackend = NullLogSettings
wouldWriteMessage _ _ = return False
makeLogger _ _ = return ()
initLogBackend _ = return NullBackend
cleanupLogBackend _ = return ()