-- | Module: $Header$ -- Description: Easy-to-use, concurrent and extendable logging framework -- Copyright: Copyright © 2010-2011 Jon Kristensen -- License: BSD-3 -- -- Maintainer: info@pontarius.org -- Stability: unstable -- Portability: portable -- | This is a work in progress for a simple logging framework that aims to be -- easy-to-use, concurrent and extendable through plug-ins. You cannot use -- this module for logging directly, instead you want to use an HLogger -- implementation. If you simply want to log messages to a file, consider -- using the @SimpleLogger@ implementation. If you want a more complicated -- logger, see below. -- -- * Implementing a Customized Logger -- -- If the loggers provided by the HLogger project (currently only -- SimpleLogger) are insufficient for your application, implementing a custom -- logging implementation on top of HLogger is simple. You can modify the -- logger behaviour (how it logs), but not the logger's API (logging levels -- and exported functions). Another limitation of HLogger implementations is -- that they are immutable (operating in a static environment, cannot have -- their state changed). -- -- See the SimpleLogger module for an example on how an implementation can be -- made. module System.Log.HLogger ( ModuleName , FunctionName , Logger (..) , LogMessage (..) , LogLevel (..) , logger ) where import Control.Concurrent (forkIO) import Control.Concurrent.Chan (Chan, newChan, writeChan) import Prelude hiding (log) -- | The name of the module issuing the logging instruction. type ModuleName = String -- | The name of the function issuing the logging instruction. type FunctionName = String -- | This object provides the logging API. Consult the documentation for the -- logging implementation (or SimpleLogger) about how to acquire a Logger -- object. data Logger = Logger { -- | Logs a message. loggerLog :: Maybe (ModuleName, FunctionName) -> LogLevel -> String -> IO () -- | Stops the logger. This action is asynchronous. , loggerStop :: IO () } -- LogLevel indicates the importance of a log entry. The log levels are the -- same as in the Syslog application. The below list is ordered by priority, -- Debug being the least significant message. data LogLevel = Debug | -- ^ Debug messages are the least significant kind -- of messages Info | -- ^ Purely informational message; consider Notice -- instead if the message is significant Notice | -- ^ Significant messages for normal conditions Warning | -- ^ Warning condition message Error | -- ^ Error condition message Critical | -- ^ Critical condition messages Alert | -- ^ Indication that action must be taken Emergency -- ^ Indication that the system is unusable deriving (Eq, Ord, Read, Show) -- | Used by logging implementations only. Contains information about the log -- message. -- TODO: Add date information? data LogMessage = LogMessage { logMessageString :: String , logMessageLevel :: LogLevel , logMessageContext :: Maybe (ModuleName, FunctionName) } -- | Used by logging implementations only. Provides a Logger object, given a -- looping function operating on a 'LogMessage' channel. logger :: (Chan (Maybe LogMessage) -> IO ()) -> IO Logger logger l = do c <- newChan forkIO $ l c return Logger { loggerLog = loggerLog_ c , loggerStop = loggerStop_ c } -- Stops the logger. This action is asynchronous. loggerStop_ :: Chan (Maybe LogMessage) -> IO () loggerStop_ c = writeChan c Nothing -- Logs a debug message. Debug messages are the least significant messages. loggerLog_ :: Chan (Maybe LogMessage) -> Maybe (ModuleName, FunctionName) -> LogLevel -> String -> IO () loggerLog_ c x l s = do writeChan c $ Just (toLogMessage x l s) return () -- Function to wrap a string and a log level into a LogMessage record. toLogMessage :: Maybe (ModuleName, FunctionName) -> LogLevel -> String -> LogMessage toLogMessage x l s = LogMessage { logMessageContext = x , logMessageLevel = l , logMessageString = s }