Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Daemon.hs @ 29a30533

History | View | Annotate | Download (13.7 kB)

1
{-| Implementation of the generic daemon functionality.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2011, 2012 Google Inc.
8

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

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Ganeti.Daemon
27
  ( DaemonOptions(..)
28
  , OptType
29
  , CheckFn
30
  , PrepFn
31
  , MainFn
32
  , defaultOptions
33
  , oShowHelp
34
  , oShowVer
35
  , oNoDaemonize
36
  , oNoUserChecks
37
  , oDebug
38
  , oPort
39
  , oBindAddress
40
  , oSyslogUsage
41
  , parseArgs
42
  , parseAddress
43
  , cleanupSocket
44
  , describeError
45
  , genericMain
46
  ) where
47

    
48
import Control.Exception
49
import Control.Monad
50
import Data.Maybe (fromMaybe)
51
import Data.Word
52
import GHC.IO.Handle (hDuplicateTo)
53
import qualified Network.Socket as Socket
54
import System.Console.GetOpt
55
import System.Exit
56
import System.Environment
57
import System.IO
58
import System.IO.Error (isDoesNotExistError, modifyIOError, annotateIOError)
59
import System.Posix.Directory
60
import System.Posix.Files
61
import System.Posix.IO
62
import System.Posix.Process
63
import System.Posix.Types
64
import System.Posix.Signals
65

    
66
import Ganeti.Common as Common
67
import Ganeti.Logging
68
import Ganeti.Runtime
69
import Ganeti.BasicTypes
70
import Ganeti.Utils
71
import qualified Ganeti.Constants as C
72
import qualified Ganeti.Ssconf as Ssconf
73

    
74
-- * Constants
75

    
76
-- | \/dev\/null path.
77
devNull :: FilePath
78
devNull = "/dev/null"
79

    
80
-- | Error message prefix, used in two separate paths (when forking
81
-- and when not).
82
daemonStartupErr :: String -> String
83
daemonStartupErr = ("Error when starting the daemon process: " ++)
84

    
85
-- * Data types
86

    
87
-- | Command line options structure.
88
data DaemonOptions = DaemonOptions
89
  { optShowHelp     :: Bool           -- ^ Just show the help
90
  , optShowVer      :: Bool           -- ^ Just show the program version
91
  , optShowComp     :: Bool           -- ^ Just show the completion info
92
  , optDaemonize    :: Bool           -- ^ Whether to daemonize or not
93
  , optPort         :: Maybe Word16   -- ^ Override for the network port
94
  , optDebug        :: Bool           -- ^ Enable debug messages
95
  , optNoUserChecks :: Bool           -- ^ Ignore user checks
96
  , optBindAddress  :: Maybe String   -- ^ Override for the bind address
97
  , optSyslogUsage  :: Maybe SyslogUsage -- ^ Override for Syslog usage
98
  }
99

    
100
-- | Default values for the command line options.
101
defaultOptions :: DaemonOptions
102
defaultOptions  = DaemonOptions
103
  { optShowHelp     = False
104
  , optShowVer      = False
105
  , optShowComp     = False
106
  , optDaemonize    = True
107
  , optPort         = Nothing
108
  , optDebug        = False
109
  , optNoUserChecks = False
110
  , optBindAddress  = Nothing
111
  , optSyslogUsage  = Nothing
112
  }
113

    
114
instance StandardOptions DaemonOptions where
115
  helpRequested = optShowHelp
116
  verRequested  = optShowVer
117
  compRequested = optShowComp
118
  requestHelp o = o { optShowHelp = True }
119
  requestVer  o = o { optShowVer  = True }
120
  requestComp o = o { optShowComp = True }
121

    
122
-- | Abrreviation for the option type.
123
type OptType = GenericOptType DaemonOptions
124

    
125
-- | Check function type.
126
type CheckFn a = DaemonOptions -> IO (Either ExitCode a)
127

    
128
-- | Prepare function type.
129
type PrepFn a b = DaemonOptions -> a -> IO b
130

    
131
-- | Main execution function type.
132
type MainFn a b = DaemonOptions -> a -> b -> IO ()
133

    
134
-- * Command line options
135

    
136
oNoDaemonize :: OptType
137
oNoDaemonize =
138
  (Option "f" ["foreground"]
139
   (NoArg (\ opts -> Ok opts { optDaemonize = False}))
140
   "Don't detach from the current terminal",
141
   OptComplNone)
142

    
143
oDebug :: OptType
144
oDebug =
145
  (Option "d" ["debug"]
146
   (NoArg (\ opts -> Ok opts { optDebug = True }))
147
   "Enable debug messages",
148
   OptComplNone)
149

    
150
oNoUserChecks :: OptType
151
oNoUserChecks =
152
  (Option "" ["no-user-checks"]
153
   (NoArg (\ opts -> Ok opts { optNoUserChecks = True }))
154
   "Ignore user checks",
155
   OptComplNone)
156

    
157
oPort :: Int -> OptType
158
oPort def =
159
  (Option "p" ["port"]
160
   (reqWithConversion (tryRead "reading port")
161
    (\port opts -> Ok opts { optPort = Just port }) "PORT")
162
   ("Network port (default: " ++ show def ++ ")"),
163
   OptComplInteger)
164

    
165
oBindAddress :: OptType
166
oBindAddress =
167
  (Option "b" ["bind"]
168
   (ReqArg (\addr opts -> Ok opts { optBindAddress = Just addr })
169
    "ADDR")
170
   "Bind address (default depends on cluster configuration)",
171
   OptComplInetAddr)
172

    
173
oSyslogUsage :: OptType
174
oSyslogUsage =
175
  (Option "" ["syslog"]
176
   (reqWithConversion syslogUsageFromRaw
177
    (\su opts -> Ok opts { optSyslogUsage = Just su })
178
    "SYSLOG")
179
   ("Enable logging to syslog (except debug \
180
    \messages); one of 'no', 'yes' or 'only' [" ++ C.syslogUsage ++
181
    "]"),
182
   OptComplChoices ["yes", "no", "only"])
183

    
184
-- | Generic options.
185
genericOpts :: [OptType]
186
genericOpts = [ oShowHelp
187
              , oShowVer
188
              , oShowComp
189
              ]
190

    
191
-- | Annotates and transforms IOErrors into a Result type. This can be
192
-- used in the error handler argument to 'catch', for example.
193
ioErrorToResult :: String -> IOError -> IO (Result a)
194
ioErrorToResult description exc =
195
  return . Bad $ description ++ ": " ++ show exc
196

    
197
-- | Small wrapper over getArgs and 'parseOpts'.
198
parseArgs :: String -> [OptType] -> IO (DaemonOptions, [String])
199
parseArgs cmd options = do
200
  cmd_args <- getArgs
201
  parseOpts defaultOptions cmd_args cmd (options ++ genericOpts) []
202

    
203
-- * Daemon-related functions
204
-- | PID file mode.
205
pidFileMode :: FileMode
206
pidFileMode = unionFileModes ownerReadMode ownerWriteMode
207

    
208
-- | Writes a PID file and locks it.
209
writePidFile :: FilePath -> IO Fd
210
writePidFile path = do
211
  fd <- createFile path pidFileMode
212
  setLock fd (WriteLock, AbsoluteSeek, 0, 0)
213
  my_pid <- getProcessID
214
  _ <- fdWrite fd (show my_pid ++ "\n")
215
  return fd
216

    
217
-- | Helper function to ensure a socket doesn't exist. Should only be
218
-- called once we have locked the pid file successfully.
219
cleanupSocket :: FilePath -> IO ()
220
cleanupSocket socketPath =
221
  catchJust (guard . isDoesNotExistError) (removeLink socketPath)
222
            (const $ return ())
223

    
224
-- | Sets up a daemon's environment.
225
setupDaemonEnv :: FilePath -> FileMode -> IO ()
226
setupDaemonEnv cwd umask = do
227
  changeWorkingDirectory cwd
228
  _ <- setFileCreationMask umask
229
  _ <- createSession
230
  return ()
231

    
232
-- | Signal handler for reopening log files.
233
handleSigHup :: FilePath -> IO ()
234
handleSigHup path = do
235
  setupDaemonFDs (Just path)
236
  logInfo "Reopening log files after receiving SIGHUP"
237

    
238
-- | Sets up a daemon's standard file descriptors.
239
setupDaemonFDs :: Maybe FilePath -> IO ()
240
setupDaemonFDs logfile = do
241
  null_in_handle <- openFile devNull ReadMode
242
  null_out_handle <- openFile (fromMaybe devNull logfile) AppendMode
243
  hDuplicateTo null_in_handle stdin
244
  hDuplicateTo null_out_handle stdout
245
  hDuplicateTo null_out_handle stderr
246
  hClose null_in_handle
247
  hClose null_out_handle
248

    
249
-- | Computes the default bind address for a given family.
250
defaultBindAddr :: Int                  -- ^ The port we want
251
                -> Socket.Family        -- ^ The cluster IP family
252
                -> Result (Socket.Family, Socket.SockAddr)
253
defaultBindAddr port Socket.AF_INET =
254
  Ok (Socket.AF_INET,
255
      Socket.SockAddrInet (fromIntegral port) Socket.iNADDR_ANY)
256
defaultBindAddr port Socket.AF_INET6 =
257
  Ok (Socket.AF_INET6,
258
      Socket.SockAddrInet6 (fromIntegral port) 0 Socket.iN6ADDR_ANY 0)
259
defaultBindAddr _ fam = Bad $ "Unsupported address family: " ++ show fam
260

    
261
-- | Default hints for the resolver
262
resolveAddrHints :: Maybe Socket.AddrInfo
263
resolveAddrHints =
264
  Just Socket.defaultHints { Socket.addrFlags = [Socket.AI_NUMERICHOST,
265
                                                 Socket.AI_NUMERICSERV] }
266

    
267
-- | Resolves a numeric address.
268
resolveAddr :: Int -> String -> IO (Result (Socket.Family, Socket.SockAddr))
269
resolveAddr port str = do
270
  resolved <- Socket.getAddrInfo resolveAddrHints (Just str) (Just (show port))
271
  return $ case resolved of
272
             [] -> Bad "Invalid results from lookup?"
273
             best:_ -> Ok (Socket.addrFamily best, Socket.addrAddress best)
274

    
275
-- | Based on the options, compute the socket address to use for the
276
-- daemon.
277
parseAddress :: DaemonOptions      -- ^ Command line options
278
             -> Int                -- ^ Default port for this daemon
279
             -> IO (Result (Socket.Family, Socket.SockAddr))
280
parseAddress opts defport = do
281
  let port = maybe defport fromIntegral $ optPort opts
282
  def_family <- Ssconf.getPrimaryIPFamily Nothing
283
  case optBindAddress opts of
284
    Nothing -> return (def_family >>= defaultBindAddr port)
285
    Just saddr -> Control.Exception.catch
286
                    (resolveAddr port saddr)
287
                    (ioErrorToResult $ "Invalid address " ++ saddr)
288

    
289
-- | Run an I\/O action that might throw an I\/O error, under a
290
-- handler that will simply annotate and re-throw the exception.
291
describeError :: String -> Maybe Handle -> Maybe FilePath -> IO a -> IO a
292
describeError descr hndl fpath =
293
  modifyIOError (\e -> annotateIOError e descr hndl fpath)
294

    
295
-- | Run an I\/O action as a daemon.
296
--
297
-- WARNING: this only works in single-threaded mode (either using the
298
-- single-threaded runtime, or using the multi-threaded one but with
299
-- only one OS thread, i.e. -N1).
300
daemonize :: FilePath -> (Maybe Fd -> IO ()) -> IO ()
301
daemonize logfile action = do
302
  (rpipe, wpipe) <- createPipe
303
  -- first fork
304
  _ <- forkProcess $ do
305
    -- in the child
306
    closeFd rpipe
307
    setupDaemonEnv "/" (unionFileModes groupModes otherModes)
308
    setupDaemonFDs $ Just logfile
309
    _ <- installHandler lostConnection (Catch (handleSigHup logfile)) Nothing
310
    -- second fork, launches the actual child code; standard
311
    -- double-fork technique
312
    _ <- forkProcess (action (Just wpipe))
313
    exitImmediately ExitSuccess
314
  closeFd wpipe
315
  hndl <- fdToHandle rpipe
316
  errors <- hGetContents hndl
317
  ecode <- if null errors
318
             then return ExitSuccess
319
             else do
320
               hPutStrLn stderr $ daemonStartupErr errors
321
               return $ ExitFailure C.exitFailure
322
  exitImmediately ecode
323

    
324
-- | Generic daemon startup.
325
genericMain :: GanetiDaemon -- ^ The daemon we're running
326
            -> [OptType]    -- ^ The available options
327
            -> CheckFn a    -- ^ Check function
328
            -> PrepFn  a b  -- ^ Prepare function
329
            -> MainFn  a b  -- ^ Execution function
330
            -> IO ()
331
genericMain daemon options check_fn prep_fn exec_fn = do
332
  let progname = daemonName daemon
333
  (opts, args) <- parseArgs progname options
334

    
335
  exitUnless (null args) "This program doesn't take any arguments"
336

    
337
  unless (optNoUserChecks opts) $ do
338
    runtimeEnts <- getEnts
339
    ents <- exitIfBad "Can't find required user/groups" runtimeEnts
340
    verifyDaemonUser daemon ents
341

    
342
  syslog <- case optSyslogUsage opts of
343
              Nothing -> exitIfBad "Invalid cluster syslog setting" $
344
                         syslogUsageFromRaw C.syslogUsage
345
              Just v -> return v
346

    
347
  log_file <- daemonLogFile daemon
348
  -- run the check function and optionally exit if it returns an exit code
349
  check_result <- check_fn opts
350
  check_result' <- case check_result of
351
                     Left code -> exitWith code
352
                     Right v -> return v
353

    
354
  let processFn = if optDaemonize opts
355
                    then daemonize log_file
356
                    else \action -> action Nothing
357
  processFn $ innerMain daemon opts syslog check_result' prep_fn exec_fn
358

    
359
-- | Full prepare function.
360
--
361
-- This is executed after daemonization, and sets up both the log
362
-- files (a generic functionality) and the custom prepare function of
363
-- the daemon.
364
fullPrep :: GanetiDaemon  -- ^ The daemon we're running
365
         -> DaemonOptions -- ^ The options structure, filled from the cmdline
366
         -> SyslogUsage   -- ^ Syslog mode
367
         -> a             -- ^ Check results
368
         -> PrepFn a b    -- ^ Prepare function
369
         -> IO b
370
fullPrep daemon opts syslog check_result prep_fn = do
371
  logfile <- if optDaemonize opts
372
               then return Nothing
373
               else liftM Just $ daemonLogFile daemon
374
  pidfile <- daemonPidFile daemon
375
  let dname = daemonName daemon
376
  setupLogging logfile dname (optDebug opts) True False syslog
377
  _ <- describeError "writing PID file; already locked?"
378
         Nothing (Just pidfile) $ writePidFile pidfile
379
  logNotice $ dname ++ " daemon startup"
380
  prep_fn opts check_result
381

    
382
-- | Inner daemon function.
383
--
384
-- This is executed after daemonization.
385
innerMain :: GanetiDaemon  -- ^ The daemon we're running
386
          -> DaemonOptions -- ^ The options structure, filled from the cmdline
387
          -> SyslogUsage   -- ^ Syslog mode
388
          -> a             -- ^ Check results
389
          -> PrepFn a b    -- ^ Prepare function
390
          -> MainFn a b    -- ^ Execution function
391
          -> Maybe Fd      -- ^ Error reporting function
392
          -> IO ()
393
innerMain daemon opts syslog check_result prep_fn exec_fn fd = do
394
  prep_result <- fullPrep daemon opts syslog check_result prep_fn
395
                 `Control.Exception.catch` handlePrepErr fd
396
  -- no error reported, we should now close the fd
397
  maybeCloseFd fd
398
  exec_fn opts check_result prep_result
399

    
400
-- | Daemon prepare error handling function.
401
handlePrepErr :: Maybe Fd -> IOError -> IO a
402
handlePrepErr fd err = do
403
  let msg = show err
404
  case fd of
405
    -- explicitly writing to the fd directly, since when forking it's
406
    -- better (safer) than trying to convert this into a full handle
407
    Just fd' -> fdWrite fd' msg >> return ()
408
    Nothing  -> hPutStrLn stderr (daemonStartupErr msg)
409
  logError msg
410
  exitWith $ ExitFailure 1
411

    
412
-- | Close a file descriptor.
413
maybeCloseFd :: Maybe Fd -> IO ()
414
maybeCloseFd Nothing   = return ()
415
maybeCloseFd (Just fd) = closeFd fd