[Haskell-cafe] Re: hslogger bugs or features?

John Goerzen jgoerzen at complete.org
Mon Feb 2 18:00:27 EST 2009


I haven't had the time to study your question in detail yet, but I would
start by directing you here:

  http://www.python.org/doc/current/library/logging.html#module-logging

hslogger is heavily based upon an earlier version of the Python logging
module.  I had some experience with it and found it to work well, and
thus based the hslogger design upon it.

-- John

Marc Weber wrote:
> Following the advice on the hslogger wiki
> (http://software.complete.org/software/wiki/hslogger)
> I'm posting my thoughts about hslogger here:
> 
> What is wired?
> This piece of code (src/System/Log/Logger.hs):
> 
>        parentHandlers name =
>             let pname = (head . drop 1 . reverse . componentsOfName) name
>                 in do 
>                 [...]
>                 next <- parentHandlers pname
>                 return ((handlers parent) ++ next)
> 
> Why?
> Because when logging to "A.B.C" it splits the String once to get
> ["A","B","C"], then it drops the last part and runs the same again for
> "A.B" and so on..
> So A string is split > 3 times for one logging action. I think this is a
> waste of cpu cycles.. I'm going to improve this. While reading the code
> i noticed two issues:
> 
> ======================================================================
> issue 1
> 
> That's not the most awkward thing:
>   When logging to "A.B.C" hslogger does add 3 loggers to the global
>   logger Map:
>   "A"
>   "A.B"
>   "A.B.C"
>   all three inheriting the default priority level of the default
>   rootLogger ""
> 
> A test application illustrating this (feature ?)
> 
>   module Main where
>   -- packages: hslogger
>   import  System.Log.Logger as HL
>   import  System.Log.Handler.Simple as HL
> 
>   main = do
>     -- the default logger logs to stderr level WARNING 
>     -- that's why the following message should be shown 
> 
>     -- a)
>     logM "A.B.C" HL.ALERT "ALERT test, should be shown and should create the sublogger"
> 
>     -- b)
>     updateGlobalLogger rootLoggerName (setLevel EMERGENCY)
> 
>     logM "A.B.C" HL.ALERT "ALERT test, should not be shown cause we have changed to EMERGENCY"
> 
> which prints:
> 
>   tmp %./test1
>   /tmp nixos   
>   ALERT test, should be shown and should create the sublogger
>   ALERT test, should not be shown cause we have changed to EMERGENCY
> 
> which is quite confusing because I haven't told hslogger explicitely
> to use a log level printing ALERTs on "A.B.C". so I'd expect that only
> the first message is shown. This behaviour is explained by the
> inheritance of the loglevel when hslogger creates them (without
> attaching handlers) automatically.
> 
> I don't want the logging behaviour depend on wether a log line has been
> emitted before or not.
> Do you agree? Have I missed something?
> 
> 
> 
> solution:
> 
> replacing
> 
>   data Logger = Logger { level :: Priority,
>                          handlers :: [HandlerT],
>                          name :: String}
> 
>   type LogTree = Map.Map String Logger
> 
> by a real log tree:
> 
>   data LogTree = LogTree {
>        level :: Priority, -- level only applies to handlers, not to subLoggers 
>        handlers :: [HandlerT],
>        subLoggers :: Map.Map String LogTree
>      }
> 
> ======================================================================
> issue 2
> 
> The second ineresting point is (bug or feature?) that you can make the
> root logger shut up by setting different log levels to sub loggers:
> 
> this sample does illustrate it:
> 
>   module Main where
>   -- packages: hslogger
>   import  System.Log.Logger as HL
>   import  System.Log.Handler.Simple as HL
> 
>   main = do
>     updateGlobalLogger "" (setLevel DEBUG)
>     updateGlobalLogger "A" (setLevel EMERGENCY)
>     logM "A" HL.ALERT "ALERT test, should not be shown cause we have
>   changed to EMERGENCY"
> 
> 
> It doesn't print anything although the default log handler on root (="")
> is set to loglever DEBUG. So there is no way to get all logmessages
> without removing all all setLevel calls to subloggers?
> Is this desirable?
> 
> ======================================================================
> my conclusion:
> 
> About issue 1 I think its a bug
> About issue 2 I don't know. I think there should be a way to get all log
> messages. So I feel this is a bug as well.
> 
> I neither have checkeg the logcxx nor log4j nor the reference
> implementation in python.
> 
> Thoughts?
> 
> Sincerly
> Marc Weber
> 



More information about the Haskell-Cafe mailing list