Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Logging.hs @ 7711f32b

History | View | Annotate | Download (4.9 kB)

1 a6e2a138 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 a6e2a138 Iustin Pop
3 ba4e38e8 Iustin Pop
{-| Implementation of the Ganeti logging functionality.
4 ba4e38e8 Iustin Pop
5 ba4e38e8 Iustin Pop
This currently lacks the following (FIXME):
6 ba4e38e8 Iustin Pop
7 ba4e38e8 Iustin Pop
- log file reopening
8 ba4e38e8 Iustin Pop
9 ba4e38e8 Iustin Pop
Note that this requires the hslogger library version 1.1 and above.
10 ba4e38e8 Iustin Pop
11 ba4e38e8 Iustin Pop
-}
12 ba4e38e8 Iustin Pop
13 ba4e38e8 Iustin Pop
{-
14 ba4e38e8 Iustin Pop
15 ce817701 Iustin Pop
Copyright (C) 2011, 2012, 2013 Google Inc.
16 ba4e38e8 Iustin Pop
17 ba4e38e8 Iustin Pop
This program is free software; you can redistribute it and/or modify
18 ba4e38e8 Iustin Pop
it under the terms of the GNU General Public License as published by
19 ba4e38e8 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
20 ba4e38e8 Iustin Pop
(at your option) any later version.
21 ba4e38e8 Iustin Pop
22 ba4e38e8 Iustin Pop
This program is distributed in the hope that it will be useful, but
23 ba4e38e8 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
24 ba4e38e8 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
25 ba4e38e8 Iustin Pop
General Public License for more details.
26 ba4e38e8 Iustin Pop
27 ba4e38e8 Iustin Pop
You should have received a copy of the GNU General Public License
28 ba4e38e8 Iustin Pop
along with this program; if not, write to the Free Software
29 ba4e38e8 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
30 ba4e38e8 Iustin Pop
02110-1301, USA.
31 ba4e38e8 Iustin Pop
32 ba4e38e8 Iustin Pop
-}
33 ba4e38e8 Iustin Pop
34 ba4e38e8 Iustin Pop
module Ganeti.Logging
35 ba4e38e8 Iustin Pop
  ( setupLogging
36 27f904f7 Petr Pudlak
  , MonadLog(..)
37 27f904f7 Petr Pudlak
  , Priority(..)
38 ba4e38e8 Iustin Pop
  , logDebug
39 ba4e38e8 Iustin Pop
  , logInfo
40 ba4e38e8 Iustin Pop
  , logNotice
41 ba4e38e8 Iustin Pop
  , logWarning
42 ba4e38e8 Iustin Pop
  , logError
43 ba4e38e8 Iustin Pop
  , logCritical
44 ba4e38e8 Iustin Pop
  , logAlert
45 ba4e38e8 Iustin Pop
  , logEmergency
46 a6e2a138 Iustin Pop
  , SyslogUsage(..)
47 a6e2a138 Iustin Pop
  , syslogUsageToRaw
48 a6e2a138 Iustin Pop
  , syslogUsageFromRaw
49 ba4e38e8 Iustin Pop
  ) where
50 ba4e38e8 Iustin Pop
51 43c329e7 Petr Pudlak
import Control.Monad
52 43c329e7 Petr Pudlak
import Control.Monad.Reader
53 ba4e38e8 Iustin Pop
import System.Log.Logger
54 ba4e38e8 Iustin Pop
import System.Log.Handler.Simple
55 a6e2a138 Iustin Pop
import System.Log.Handler.Syslog
56 a6e2a138 Iustin Pop
import System.Log.Handler (setFormatter, LogHandler)
57 ba4e38e8 Iustin Pop
import System.Log.Formatter
58 ba4e38e8 Iustin Pop
import System.IO
59 ba4e38e8 Iustin Pop
60 a6e2a138 Iustin Pop
import Ganeti.THH
61 df726590 Jose A. Lopes
import qualified Ganeti.ConstantUtils as ConstantUtils
62 ba4e38e8 Iustin Pop
63 a6e2a138 Iustin Pop
-- | Syslog usage type.
64 df726590 Jose A. Lopes
$(declareLADT ''String "SyslogUsage"
65 df726590 Jose A. Lopes
  [ ("SyslogNo",   "no")
66 df726590 Jose A. Lopes
  , ("SyslogYes",  "yes")
67 df726590 Jose A. Lopes
  , ("SyslogOnly", "only")
68 a6e2a138 Iustin Pop
  ])
69 a6e2a138 Iustin Pop
70 ba4e38e8 Iustin Pop
-- | Builds the log formatter.
71 ba4e38e8 Iustin Pop
logFormatter :: String  -- ^ Program
72 ba4e38e8 Iustin Pop
             -> Bool    -- ^ Multithreaded
73 ba4e38e8 Iustin Pop
             -> Bool    -- ^ Syslog
74 ba4e38e8 Iustin Pop
             -> LogFormatter a
75 ba4e38e8 Iustin Pop
logFormatter prog mt syslog =
76 ba4e38e8 Iustin Pop
  let parts = [ if syslog
77 ba4e38e8 Iustin Pop
                  then "[$pid]:"
78 ba4e38e8 Iustin Pop
                  else "$time: " ++ prog ++ " pid=$pid"
79 ba4e38e8 Iustin Pop
              , if mt then if syslog then " ($tid)" else "/$tid"
80 ba4e38e8 Iustin Pop
                  else ""
81 ba4e38e8 Iustin Pop
              , " $prio $msg"
82 ba4e38e8 Iustin Pop
              ]
83 ce817701 Iustin Pop
  in tfLogFormatter "%F %X,%q %Z" $ concat parts
84 ba4e38e8 Iustin Pop
85 a6e2a138 Iustin Pop
-- | Helper to open and set the formatter on a log if enabled by a
86 a6e2a138 Iustin Pop
-- given condition, otherwise returning an empty list.
87 a6e2a138 Iustin Pop
openFormattedHandler :: (LogHandler a) => Bool
88 a6e2a138 Iustin Pop
                     -> LogFormatter a -> IO a -> IO [a]
89 a6e2a138 Iustin Pop
openFormattedHandler False _ _ = return []
90 a6e2a138 Iustin Pop
openFormattedHandler True fmt opener = do
91 a6e2a138 Iustin Pop
  handler <- opener
92 a6e2a138 Iustin Pop
  return [setFormatter handler fmt]
93 a6e2a138 Iustin Pop
94 ba4e38e8 Iustin Pop
-- | Sets up the logging configuration.
95 0c28bee1 Iustin Pop
setupLogging :: Maybe String    -- ^ Log file
96 ba4e38e8 Iustin Pop
             -> String    -- ^ Program name
97 ba4e38e8 Iustin Pop
             -> Bool      -- ^ Debug level
98 ba4e38e8 Iustin Pop
             -> Bool      -- ^ Log to stderr
99 ba4e38e8 Iustin Pop
             -> Bool      -- ^ Log to console
100 a6e2a138 Iustin Pop
             -> SyslogUsage -- ^ Syslog usage
101 ba4e38e8 Iustin Pop
             -> IO ()
102 a6e2a138 Iustin Pop
setupLogging logf program debug stderr_logging console syslog = do
103 ba4e38e8 Iustin Pop
  let level = if debug then DEBUG else INFO
104 df726590 Jose A. Lopes
      destf = if console then Just ConstantUtils.devConsole else logf
105 ba4e38e8 Iustin Pop
      fmt = logFormatter program False False
106 0c28bee1 Iustin Pop
      file_logging = syslog /= SyslogOnly
107 ba4e38e8 Iustin Pop
108 ba4e38e8 Iustin Pop
  updateGlobalLogger rootLoggerName (setLevel level)
109 ba4e38e8 Iustin Pop
110 a6e2a138 Iustin Pop
  stderr_handlers <- openFormattedHandler stderr_logging fmt $
111 a6e2a138 Iustin Pop
                     streamHandler stderr level
112 a6e2a138 Iustin Pop
113 0c28bee1 Iustin Pop
  file_handlers <- case destf of
114 0c28bee1 Iustin Pop
                     Nothing -> return []
115 0c28bee1 Iustin Pop
                     Just path -> openFormattedHandler file_logging fmt $
116 0c28bee1 Iustin Pop
                                  fileHandler path level
117 a6e2a138 Iustin Pop
118 2cdaf225 Iustin Pop
  let handlers = file_handlers ++ stderr_handlers
119 ba4e38e8 Iustin Pop
  updateGlobalLogger rootLoggerName $ setHandlers handlers
120 a6e2a138 Iustin Pop
  -- syslog handler is special (another type, still instance of the
121 a6e2a138 Iustin Pop
  -- typeclass, and has a built-in formatter), so we can't pass it in
122 a6e2a138 Iustin Pop
  -- the above list
123 a6e2a138 Iustin Pop
  when (syslog /= SyslogNo) $ do
124 a6e2a138 Iustin Pop
    syslog_handler <- openlog program [PID] DAEMON INFO
125 a6e2a138 Iustin Pop
    updateGlobalLogger rootLoggerName $ addHandler syslog_handler
126 ba4e38e8 Iustin Pop
127 ba4e38e8 Iustin Pop
-- * Logging function aliases
128 ba4e38e8 Iustin Pop
129 27f904f7 Petr Pudlak
-- | A monad that allows logging.
130 27f904f7 Petr Pudlak
class Monad m => MonadLog m where
131 27f904f7 Petr Pudlak
  -- | Log at a given level.
132 27f904f7 Petr Pudlak
  logAt :: Priority -> String -> m ()
133 27f904f7 Petr Pudlak
134 27f904f7 Petr Pudlak
instance MonadLog IO where
135 27f904f7 Petr Pudlak
  logAt = logM rootLoggerName
136 27f904f7 Petr Pudlak
137 43c329e7 Petr Pudlak
instance (MonadLog m) => MonadLog (ReaderT r m) where
138 43c329e7 Petr Pudlak
  logAt p x = lift $ logAt p x
139 27f904f7 Petr Pudlak
140 ba4e38e8 Iustin Pop
-- | Log at debug level.
141 27f904f7 Petr Pudlak
logDebug :: (MonadLog m) => String -> m ()
142 27f904f7 Petr Pudlak
logDebug = logAt DEBUG
143 ba4e38e8 Iustin Pop
144 ba4e38e8 Iustin Pop
-- | Log at info level.
145 27f904f7 Petr Pudlak
logInfo :: (MonadLog m) => String -> m ()
146 27f904f7 Petr Pudlak
logInfo = logAt INFO
147 ba4e38e8 Iustin Pop
148 ba4e38e8 Iustin Pop
-- | Log at notice level.
149 27f904f7 Petr Pudlak
logNotice :: (MonadLog m) => String -> m ()
150 27f904f7 Petr Pudlak
logNotice = logAt NOTICE
151 ba4e38e8 Iustin Pop
152 ba4e38e8 Iustin Pop
-- | Log at warning level.
153 27f904f7 Petr Pudlak
logWarning :: (MonadLog m) => String -> m ()
154 27f904f7 Petr Pudlak
logWarning = logAt WARNING
155 ba4e38e8 Iustin Pop
156 ba4e38e8 Iustin Pop
-- | Log at error level.
157 27f904f7 Petr Pudlak
logError :: (MonadLog m) => String -> m ()
158 27f904f7 Petr Pudlak
logError = logAt ERROR
159 ba4e38e8 Iustin Pop
160 ba4e38e8 Iustin Pop
-- | Log at critical level.
161 27f904f7 Petr Pudlak
logCritical :: (MonadLog m) => String -> m ()
162 27f904f7 Petr Pudlak
logCritical = logAt CRITICAL
163 ba4e38e8 Iustin Pop
164 ba4e38e8 Iustin Pop
-- | Log at alert level.
165 27f904f7 Petr Pudlak
logAlert :: (MonadLog m) => String -> m ()
166 27f904f7 Petr Pudlak
logAlert = logAt ALERT
167 ba4e38e8 Iustin Pop
168 ba4e38e8 Iustin Pop
-- | Log at emergency level.
169 27f904f7 Petr Pudlak
logEmergency :: (MonadLog m) => String -> m ()
170 27f904f7 Petr Pudlak
logEmergency = logAt EMERGENCY