Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Logging.hs @ 78e0f701

History | View | Annotate | Download (6.1 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 qualified Control.Monad.State.Strict as SS
59
import Control.Monad.Trans.Identity
60
import Data.Monoid
61
import System.Log.Logger
62
import System.Log.Handler.Simple
63
import System.Log.Handler.Syslog
64
import System.Log.Handler (setFormatter, LogHandler)
65
import System.Log.Formatter
66
import System.IO
67

    
68
import Ganeti.BasicTypes (ResultT(..))
69
import Ganeti.THH
70
import qualified Ganeti.ConstantUtils as ConstantUtils
71

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

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

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

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

    
117
  updateGlobalLogger rootLoggerName (setLevel level)
118

    
119
  stderr_handlers <- openFormattedHandler stderr_logging fmt $
120
                     streamHandler stderr level
121

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

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

    
136
-- * Logging function aliases
137

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

    
143
instance MonadLog IO where
144
  logAt = logM rootLoggerName
145

    
146
instance (MonadLog m) => MonadLog (IdentityT m) where
147
  logAt p = lift . logAt p
148

    
149
instance (MonadLog m) => MonadLog (ReaderT r m) where
150
  logAt p = lift . logAt p
151

    
152
instance (MonadLog m) => MonadLog (SS.StateT s m) where
153
  logAt p = lift . logAt p
154

    
155
instance (MonadLog m, Monoid w) => MonadLog (RWSS.RWST r w s m) where
156
  logAt p = lift . logAt p
157

    
158
instance (MonadLog m, Error e) => MonadLog (ResultT e m) where
159
  logAt p = lift . logAt p
160

    
161
-- | Log at debug level.
162
logDebug :: (MonadLog m) => String -> m ()
163
logDebug = logAt DEBUG
164

    
165
-- | Log at info level.
166
logInfo :: (MonadLog m) => String -> m ()
167
logInfo = logAt INFO
168

    
169
-- | Log at notice level.
170
logNotice :: (MonadLog m) => String -> m ()
171
logNotice = logAt NOTICE
172

    
173
-- | Log at warning level.
174
logWarning :: (MonadLog m) => String -> m ()
175
logWarning = logAt WARNING
176

    
177
-- | Log at error level.
178
logError :: (MonadLog m) => String -> m ()
179
logError = logAt ERROR
180

    
181
-- | Log at critical level.
182
logCritical :: (MonadLog m) => String -> m ()
183
logCritical = logAt CRITICAL
184

    
185
-- | Log at alert level.
186
logAlert :: (MonadLog m) => String -> m ()
187
logAlert = logAt ALERT
188

    
189
-- | Log at emergency level.
190
logEmergency :: (MonadLog m) => String -> m ()
191
logEmergency = logAt EMERGENCY
192

    
193
-- | Check if the logging is at DEBUG level.
194
-- DEBUG logging is unacceptable for production.
195
isDebugMode :: IO Bool
196
isDebugMode = (Just DEBUG ==) . getLevel <$> getRootLogger
197

    
198
-- * Logging in an error monad with rethrowing errors
199

    
200
-- | If an error occurs within a given computation, it annotated
201
-- with a given message and logged and the error is re-thrown.
202
withErrorLogAt :: (MonadLog m, MonadError e m, Show e)
203
               => Priority -> String -> m a -> m a
204
withErrorLogAt prio msg = flip catchError $ \e -> do
205
  logAt prio (msg ++ ": " ++ show e)
206
  throwError e