Copyright | Copyright (C) 2004-2011 John Goerzen |
---|---|
License | BSD3 |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Haskell Logging Framework, Primary Interface
Written by John Goerzen, jgoerzen@complete.org
Welcome to the error and information logging system for Haskell.
This system is patterned after Python's logging
module,
http://www.python.org/doc/current/lib/module-logging.html and some of
the documentation here was based on documentation there.
To log a message, you perform operations on Logger
s. Each Logger
has a
name, and they are arranged hierarchically. Periods serve as separators.
Therefore, a Logger
named "foo" is the parent of loggers "foo.printing",
"foo.html", and "foo.io". These names can be anything you want. They're
used to indicate the area of an application or library in which a logged
message originates. Later you will see how you can use this concept to
fine-tune logging behaviors based on specific application areas.
You can also tune logging behaviors based upon how important a message is.
Each message you log will have an importance associated with it. The different
importance levels are given by the Priority
type. I've also provided
some convenient functions that correspond to these importance levels:
debugM
through emergencyM
log messages with the specified importance.
Now, an importance level (or Priority
)
is associated not just with a particular message but also
with a Logger
. If the Priority
of a given log message is lower than
the Priority
configured in the Logger
, that message is ignored. This
way, you can globally control how verbose your logging output is.
Now, let's follow what happens under the hood when you log a message. We'll
assume for the moment that you are logging something with a high enough
Priority
that it passes the test in your Logger
. In your code, you'll
call logM
or something like debugM
to log the message. Your Logger
decides to accept the message. What next?
Well, we also have a notion of handlers (LogHandler
s, to be precise).
A LogHandler
is a thing that takes a message and sends it somewhere.
That "somewhere" may be your screen (via standard error), your system's
logging infrastructure (via syslog), a file, or other things. Each
Logger
can have zero or more LogHandler
s associated with it. When your
Logger
has a message to log, it passes it to every LogHandler
it knows
of to process. What's more, it is also passed to /all handlers of all
ancestors of the Logger/, regardless of whether those Logger
s would
normally have passed on the message.
Each Logger
can optionally store a Priority
. If a given Logger does
not have a Priority, and you log a message to that logger, the system will
use the priority of the parent of the destination logger to find out whether
to log the message. If the parent has no priority associated with it,
the system continues walking up the tree to figure out a priority until
it hits the root logger. In this way, you can easily adjust the priority
of an entire subtree of loggers. When a new logger is created, it has no
priority by default. The exception is the root logger, which has a WARNING
priority by default.
To give you one extra little knob to turn, LogHandler
s can also have
importance levels (Priority
) associated with them in the same way
that Logger
s do. They act just like the Priority
value in the
Logger
s -- as a filter. It's useful, for instance, to make sure that
under no circumstances will a mere DEBUG
message show up in your syslog.
There are three built-in handlers given in two built-in modules: System.Log.Handler.Simple and System.Log.Handler.Syslog.
There is a special logger known as the root logger that sits at the top
of the logger hierarchy. It is always present, and handlers attached
there will be called for every message. You can use getRootLogger
to get
it or rootLoggerName
to work with it by name.
The formatting of log messages may be customized by setting a LogFormatter
on the desired LogHandler
. There are a number of simple formatters defined
in System.Log.Formatter, which may be used directly, or extend to create
your own formatter.
Here's an example to illustrate some of these concepts:
import System.Log.Logger import System.Log.Handler.Syslog import System.Log.Handler.Simple import System.Log.Handler (setFormatter) import System.Log.Formatter -- By default, all messages of level WARNING and above are sent to stderr. -- Everything else is ignored. -- "MyApp.Component" is an arbitrary string; you can tune -- logging behavior based on it later. main = do debugM "MyApp.Component" "This is a debug message -- never to be seen" warningM "MyApp.Component2" "Something Bad is about to happen." -- Copy everything to syslog from here on out. s <- openlog "SyslogStuff" [PID] USER DEBUG updateGlobalLogger rootLoggerName (addHandler s) errorM "MyApp.Component" "This is going to stderr and syslog." -- Now we'd like to see everything from BuggyComponent -- at DEBUG or higher go to syslog and stderr. -- Also, we'd like to still ignore things less than -- WARNING in other areas. -- -- So, we adjust the Logger for MyApp.BuggyComponent. updateGlobalLogger "MyApp.BuggyComponent" (setLevel DEBUG) -- This message will go to syslog and stderr debugM "MyApp.BuggyComponent" "This buggy component is buggy" -- This message will go to syslog and stderr too. warningM "MyApp.BuggyComponent" "Still Buggy" -- This message goes nowhere. debugM "MyApp.WorkingComponent" "Hello" -- Now we decide we'd also like to log everything from BuggyComponent at DEBUG -- or higher to a file for later diagnostics. We'd also like to customize the -- format of the log message, so we use a 'simpleLogFormatter' h <- fileHandler "debug.log" DEBUG >>= \lh -> return $ setFormatter lh (simpleLogFormatter "[$time : $loggername : $prio] $msg") updateGlobalLogger "MyApp.BuggyComponent" (addHandler h) -- This message will go to syslog and stderr, -- and to the file "debug.log" with a format like : -- [2010-05-23 16:47:28 : MyApp.BuggyComponent : DEBUG] Some useful diagnostics... debugM "MyApp.BuggyComponent" "Some useful diagnostics..."
Synopsis
- data Logger
- data Priority
- logM :: String -> Priority -> String -> IO ()
- debugM :: String -> String -> IO ()
- infoM :: String -> String -> IO ()
- noticeM :: String -> String -> IO ()
- warningM :: String -> String -> IO ()
- errorM :: String -> String -> IO ()
- criticalM :: String -> String -> IO ()
- alertM :: String -> String -> IO ()
- emergencyM :: String -> String -> IO ()
- removeAllHandlers :: IO ()
- traplogging :: String -> Priority -> String -> IO a -> IO a
- logL :: Logger -> Priority -> String -> IO ()
- getLogger :: String -> IO Logger
- getRootLogger :: IO Logger
- rootLoggerName :: String
- addHandler :: LogHandler a => a -> Logger -> Logger
- removeHandler :: Logger -> Logger
- setHandlers :: LogHandler a => [a] -> Logger -> Logger
- getLevel :: Logger -> Maybe Priority
- setLevel :: Priority -> Logger -> Logger
- clearLevel :: Logger -> Logger
- saveGlobalLogger :: Logger -> IO ()
- updateGlobalLogger :: String -> (Logger -> Logger) -> IO ()
Basic Types
Re-Exported from System.Log
Priorities are used to define how important a log message is. Users can filter log messages based on priorities.
These have their roots on the traditional syslog system. The standard definitions are given below, but you are free to interpret them however you like. They are listed here in ascending importance order.
DEBUG | Debug messages |
INFO | Information |
NOTICE | Normal runtime conditions |
WARNING | General Warnings |
ERROR | General Errors |
CRITICAL | Severe situations |
ALERT | Take immediate action |
EMERGENCY | System is unusable |
Instances
Bounded Priority Source # | |
Enum Priority Source # | |
Eq Priority Source # | |
Data Priority Source # | |
Defined in System.Log gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Priority -> c Priority # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Priority # toConstr :: Priority -> Constr # dataTypeOf :: Priority -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Priority) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Priority) # gmapT :: (forall b. Data b => b -> b) -> Priority -> Priority # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Priority -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Priority -> r # gmapQ :: (forall d. Data d => d -> u) -> Priority -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Priority -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Priority -> m Priority # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Priority -> m Priority # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Priority -> m Priority # | |
Ord Priority Source # | |
Read Priority Source # | |
Show Priority Source # | |
Generic Priority Source # | |
NFData Priority Source # | Since: 1.3.1.0 |
Defined in System.Log | |
type Rep Priority Source # | |
Defined in System.Log type Rep Priority = D1 (MetaData "Priority" "System.Log" "hslogger-1.3.1.0-DmGQNXFaR77Fqc2qmwKhmf" False) (((C1 (MetaCons "DEBUG" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "INFO" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "NOTICE" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "WARNING" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "ERROR" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CRITICAL" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "ALERT" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "EMERGENCY" PrefixI False) (U1 :: Type -> Type)))) |
Logging Messages
Basic
:: String | Name of the logger to use |
-> Priority | Priority of this message |
-> String | The log text itself |
-> IO () |
Log a message using the given logger at a given priority.
Utility Functions
Log a message at CRITICAL
priority
Log a message at EMERGENCY
priority
removeAllHandlers :: IO () Source #
Allow graceful shutdown. Release all opened fileshandlersetc.
traplogging :: String -> Priority -> String -> IO a -> IO a Source #
Traps exceptions that may occur, logging them, then passing them on.
Takes a logger name, priority, leading description text (you can set it to
""
if you don't want any), and action to run.
Logging to a particular Logger by object
logL :: Logger -> Priority -> String -> IO () Source #
Log a message, assuming the current logger's level permits it.
Logger Manipulation
These functions help you work with loggers. There are some special things to be aware of.
First of all, whenever you first access a given logger by name, it
magically springs to life. It has a default Priority
of Nothing
and an empty handler list -- which means that it will inherit whatever its
parents do.
Finding / Creating Loggers
getLogger :: String -> IO Logger Source #
Returns the logger for the given name. If no logger with that name exists, creates new loggers and any necessary parent loggers, with no connected handlers.
getRootLogger :: IO Logger Source #
Returns the root logger.
rootLoggerName :: String Source #
This is the base class for the various log handlers. They should all adhere to this class.
The name of the root logger, which is always defined and present on the system.
Modifying Loggers
Keep in mind that "modification" here is modification in the Haskell
sense. We do not actually cause mutation in a specific Logger
. Rather,
we return you a new Logger
object with the change applied.
Also, please note that these functions will not have an effect on the
global Logger
hierarchy. You may use your new Logger
s locally,
but other functions won't see the changes. To make a change global,
you'll need to use updateGlobalLogger
or saveGlobalLogger
.
addHandler :: LogHandler a => a -> Logger -> Logger Source #
removeHandler :: Logger -> Logger Source #
Remove a handler from the Logger
. Handlers are removed in the reverse
order they were added, so the following property holds for any LogHandler
h
:
removeHandler . addHandler h = id
If no handlers are associated with the Logger
, it is returned unchanged.
The root logger's default handler that writes every message to stderr can be removed by using this function before any handlers have been added to the root logger:
updateGlobalLogger rootLoggerName removeHandler
setHandlers :: LogHandler a => [a] -> Logger -> Logger Source #
Set the 'Logger'\'s list of handlers to the list supplied. All existing handlers are removed first.
getLevel :: Logger -> Maybe Priority Source #
Returns the "level" of the logger. Items beneath this level will be ignored.
clearLevel :: Logger -> Logger Source #
Clears the "level" of the Logger
. It will now inherit the level of
| its parent.
Saving Your Changes
These functions commit changes you've made to loggers to the global logger hierarchy.
saveGlobalLogger :: Logger -> IO () Source #
Updates the global record for the given logger to take into account any changes you may have made.
Helps you make changes on the given logger. Takes a function
that makes changes and writes those changes back to the global
database. Here's an example from above ("s" is a LogHandler
):
updateGlobalLogger "MyApp.BuggyComponent" (setLevel DEBUG . setHandlers [s])