Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Logging.hs @ 3062d395

History | View | Annotate | Download (5.7 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of the Ganeti logging functionality.
4

    
5
This currently lacks the following (FIXME):
6

    
7
- log file reopening
8

    
9
Note that this requires the hslogger library version 1.1 and above.
10

    
11
-}
12

    
13
{-
14

    
15
Copyright (C) 2011, 2012, 2013 Google Inc.
16

    
17
This program is free software; you can redistribute it and/or modify
18
it under the terms of the GNU General Public License as published by
19
the Free Software Foundation; either version 2 of the License, or
20
(at your option) any later version.
21

    
22
This program is distributed in the hope that it will be useful, but
23
WITHOUT ANY WARRANTY; without even the implied warranty of
24
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
25
General Public License for more details.
26

    
27
You should have received a copy of the GNU General Public License
28
along with this program; if not, write to the Free Software
29
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
30
02110-1301, USA.
31

    
32
-}
33

    
34
module Ganeti.Logging
35
  ( setupLogging
36
  , MonadLog(..)
37
  , Priority(..)
38
  , logDebug
39
  , logInfo
40
  , logNotice
41
  , logWarning
42
  , logError
43
  , logCritical
44
  , logAlert
45
  , logEmergency
46
  , SyslogUsage(..)
47
  , syslogUsageToRaw
48
  , syslogUsageFromRaw
49
  , withErrorLogAt
50
  , isDebugMode
51
  ) where
52

    
53
import Control.Applicative ((<$>))
54
import Control.Monad
55
import Control.Monad.Error (Error(..), MonadError(..), catchError)
56
import Control.Monad.Reader
57
import System.Log.Logger
58
import System.Log.Handler.Simple
59
import System.Log.Handler.Syslog
60
import System.Log.Handler (setFormatter, LogHandler)
61
import System.Log.Formatter
62
import System.IO
63

    
64
import Ganeti.BasicTypes (ResultT(..))
65
import Ganeti.THH
66
import qualified Ganeti.ConstantUtils as ConstantUtils
67

    
68
-- | Syslog usage type.
69
$(declareLADT ''String "SyslogUsage"
70
  [ ("SyslogNo",   "no")
71
  , ("SyslogYes",  "yes")
72
  , ("SyslogOnly", "only")
73
  ])
74

    
75
-- | Builds the log formatter.
76
logFormatter :: String  -- ^ Program
77
             -> Bool    -- ^ Multithreaded
78
             -> Bool    -- ^ Syslog
79
             -> LogFormatter a
80
logFormatter prog mt syslog =
81
  let parts = [ if syslog
82
                  then "[$pid]:"
83
                  else "$time: " ++ prog ++ " pid=$pid"
84
              , if mt then if syslog then " ($tid)" else "/$tid"
85
                  else ""
86
              , " $prio $msg"
87
              ]
88
  in tfLogFormatter "%F %X,%q %Z" $ concat parts
89

    
90
-- | Helper to open and set the formatter on a log if enabled by a
91
-- given condition, otherwise returning an empty list.
92
openFormattedHandler :: (LogHandler a) => Bool
93
                     -> LogFormatter a -> IO a -> IO [a]
94
openFormattedHandler False _ _ = return []
95
openFormattedHandler True fmt opener = do
96
  handler <- opener
97
  return [setFormatter handler fmt]
98

    
99
-- | Sets up the logging configuration.
100
setupLogging :: Maybe String    -- ^ Log file
101
             -> String    -- ^ Program name
102
             -> Bool      -- ^ Debug level
103
             -> Bool      -- ^ Log to stderr
104
             -> Bool      -- ^ Log to console
105
             -> SyslogUsage -- ^ Syslog usage
106
             -> IO ()
107
setupLogging logf program debug stderr_logging console syslog = do
108
  let level = if debug then DEBUG else INFO
109
      destf = if console then Just ConstantUtils.devConsole else logf
110
      fmt = logFormatter program False False
111
      file_logging = syslog /= SyslogOnly
112

    
113
  updateGlobalLogger rootLoggerName (setLevel level)
114

    
115
  stderr_handlers <- openFormattedHandler stderr_logging fmt $
116
                     streamHandler stderr level
117

    
118
  file_handlers <- case destf of
119
                     Nothing -> return []
120
                     Just path -> openFormattedHandler file_logging fmt $
121
                                  fileHandler path level
122

    
123
  let handlers = file_handlers ++ stderr_handlers
124
  updateGlobalLogger rootLoggerName $ setHandlers handlers
125
  -- syslog handler is special (another type, still instance of the
126
  -- typeclass, and has a built-in formatter), so we can't pass it in
127
  -- the above list
128
  when (syslog /= SyslogNo) $ do
129
    syslog_handler <- openlog program [PID] DAEMON INFO
130
    updateGlobalLogger rootLoggerName $ addHandler syslog_handler
131

    
132
-- * Logging function aliases
133

    
134
-- | A monad that allows logging.
135
class Monad m => MonadLog m where
136
  -- | Log at a given level.
137
  logAt :: Priority -> String -> m ()
138

    
139
instance MonadLog IO where
140
  logAt = logM rootLoggerName
141

    
142
instance (MonadLog m) => MonadLog (ReaderT r m) where
143
  logAt p = lift . logAt p
144

    
145
instance (MonadLog m, Error e) => MonadLog (ResultT e m) where
146
  logAt p = lift . logAt p
147

    
148
-- | Log at debug level.
149
logDebug :: (MonadLog m) => String -> m ()
150
logDebug = logAt DEBUG
151

    
152
-- | Log at info level.
153
logInfo :: (MonadLog m) => String -> m ()
154
logInfo = logAt INFO
155

    
156
-- | Log at notice level.
157
logNotice :: (MonadLog m) => String -> m ()
158
logNotice = logAt NOTICE
159

    
160
-- | Log at warning level.
161
logWarning :: (MonadLog m) => String -> m ()
162
logWarning = logAt WARNING
163

    
164
-- | Log at error level.
165
logError :: (MonadLog m) => String -> m ()
166
logError = logAt ERROR
167

    
168
-- | Log at critical level.
169
logCritical :: (MonadLog m) => String -> m ()
170
logCritical = logAt CRITICAL
171

    
172
-- | Log at alert level.
173
logAlert :: (MonadLog m) => String -> m ()
174
logAlert = logAt ALERT
175

    
176
-- | Log at emergency level.
177
logEmergency :: (MonadLog m) => String -> m ()
178
logEmergency = logAt EMERGENCY
179

    
180
-- | Check if the logging is at DEBUG level.
181
-- DEBUG logging is unacceptable for production.
182
isDebugMode :: IO Bool
183
isDebugMode = (Just DEBUG ==) . getLevel <$> getRootLogger
184

    
185
-- * Logging in an error monad with rethrowing errors
186

    
187
-- | If an error occurs within a given computation, it annotated
188
-- with a given message and logged and the error is re-thrown.
189
withErrorLogAt :: (MonadLog m, MonadError e m, Show e)
190
               => Priority -> String -> m a -> m a
191
withErrorLogAt prio msg = flip catchError $ \e -> do
192
  logAt prio (msg ++ ": " ++ show e)
193
  throwError e