Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Logging.hs @ 12121213

History | View | Annotate | Download (5.9 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 qualified Control.Monad.RWS.Strict as RWSS
58
import Data.Monoid
59
import System.Log.Logger
60
import System.Log.Handler.Simple
61
import System.Log.Handler.Syslog
62
import System.Log.Handler (setFormatter, LogHandler)
63
import System.Log.Formatter
64
import System.IO
65

    
66
import Ganeti.BasicTypes (ResultT(..))
67
import Ganeti.THH
68
import qualified Ganeti.ConstantUtils as ConstantUtils
69

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

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

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

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

    
115
  updateGlobalLogger rootLoggerName (setLevel level)
116

    
117
  stderr_handlers <- openFormattedHandler stderr_logging fmt $
118
                     streamHandler stderr level
119

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

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

    
134
-- * Logging function aliases
135

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

    
141
instance MonadLog IO where
142
  logAt = logM rootLoggerName
143

    
144
instance (MonadLog m) => MonadLog (ReaderT r m) where
145
  logAt p = lift . logAt p
146

    
147
instance (MonadLog m, Monoid w) => MonadLog (RWSS.RWST r w s m) where
148
  logAt p = lift . logAt p
149

    
150
instance (MonadLog m, Error e) => MonadLog (ResultT e m) where
151
  logAt p = lift . logAt p
152

    
153
-- | Log at debug level.
154
logDebug :: (MonadLog m) => String -> m ()
155
logDebug = logAt DEBUG
156

    
157
-- | Log at info level.
158
logInfo :: (MonadLog m) => String -> m ()
159
logInfo = logAt INFO
160

    
161
-- | Log at notice level.
162
logNotice :: (MonadLog m) => String -> m ()
163
logNotice = logAt NOTICE
164

    
165
-- | Log at warning level.
166
logWarning :: (MonadLog m) => String -> m ()
167
logWarning = logAt WARNING
168

    
169
-- | Log at error level.
170
logError :: (MonadLog m) => String -> m ()
171
logError = logAt ERROR
172

    
173
-- | Log at critical level.
174
logCritical :: (MonadLog m) => String -> m ()
175
logCritical = logAt CRITICAL
176

    
177
-- | Log at alert level.
178
logAlert :: (MonadLog m) => String -> m ()
179
logAlert = logAt ALERT
180

    
181
-- | Log at emergency level.
182
logEmergency :: (MonadLog m) => String -> m ()
183
logEmergency = logAt EMERGENCY
184

    
185
-- | Check if the logging is at DEBUG level.
186
-- DEBUG logging is unacceptable for production.
187
isDebugMode :: IO Bool
188
isDebugMode = (Just DEBUG ==) . getLevel <$> getRootLogger
189

    
190
-- * Logging in an error monad with rethrowing errors
191

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