Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (15.8 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.Concurrent
49
import Control.Exception
50
import Control.Monad
51
import Data.Maybe (fromMaybe, listToMaybe)
52
import Text.Printf
53
import Data.Word
54
import GHC.IO.Handle (hDuplicateTo)
55
import Network.BSD (getHostName)
56
import qualified Network.Socket as Socket
57
import System.Console.GetOpt
58
import System.Directory
59
import System.Exit
60
import System.Environment
61
import System.IO
62
import System.IO.Error (isDoesNotExistError, modifyIOError, annotateIOError)
63
import System.Posix.Directory
64
import System.Posix.Files
65
import System.Posix.IO
66
import System.Posix.Process
67
import System.Posix.Types
68
import System.Posix.Signals
69

    
70
import Ganeti.Common as Common
71
import Ganeti.Logging
72
import Ganeti.Runtime
73
import Ganeti.BasicTypes
74
import Ganeti.Utils
75
import qualified Ganeti.Constants as C
76
import qualified Ganeti.Ssconf as Ssconf
77

    
78
-- * Constants
79

    
80
-- | \/dev\/null path.
81
devNull :: FilePath
82
devNull = "/dev/null"
83

    
84
-- | Error message prefix, used in two separate paths (when forking
85
-- and when not).
86
daemonStartupErr :: String -> String
87
daemonStartupErr = ("Error when starting the daemon process: " ++)
88

    
89
-- * Data types
90

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

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

    
118
instance StandardOptions DaemonOptions where
119
  helpRequested = optShowHelp
120
  verRequested  = optShowVer
121
  compRequested = optShowComp
122
  requestHelp o = o { optShowHelp = True }
123
  requestVer  o = o { optShowVer  = True }
124
  requestComp o = o { optShowComp = True }
125

    
126
-- | Abrreviation for the option type.
127
type OptType = GenericOptType DaemonOptions
128

    
129
-- | Check function type.
130
type CheckFn a = DaemonOptions -> IO (Either ExitCode a)
131

    
132
-- | Prepare function type.
133
type PrepFn a b = DaemonOptions -> a -> IO b
134

    
135
-- | Main execution function type.
136
type MainFn a b = DaemonOptions -> a -> b -> IO ()
137

    
138
-- * Command line options
139

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

    
147
oDebug :: OptType
148
oDebug =
149
  (Option "d" ["debug"]
150
   (NoArg (\ opts -> Ok opts { optDebug = True }))
151
   "Enable debug messages",
152
   OptComplNone)
153

    
154
oNoUserChecks :: OptType
155
oNoUserChecks =
156
  (Option "" ["no-user-checks"]
157
   (NoArg (\ opts -> Ok opts { optNoUserChecks = True }))
158
   "Ignore user checks",
159
   OptComplNone)
160

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

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

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

    
188
-- | Generic options.
189
genericOpts :: [OptType]
190
genericOpts = [ oShowHelp
191
              , oShowVer
192
              , oShowComp
193
              ]
194

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

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

    
207
-- * Daemon-related functions
208

    
209
-- | PID file mode.
210
pidFileMode :: FileMode
211
pidFileMode = unionFileModes ownerReadMode ownerWriteMode
212

    
213
-- | PID file open flags.
214
pidFileFlags :: OpenFileFlags
215
pidFileFlags = defaultFileFlags { noctty = True, trunc = False }
216

    
217
-- | Writes a PID file and locks it.
218
writePidFile :: FilePath -> IO Fd
219
writePidFile path = do
220
  fd <- openFd path ReadWrite (Just pidFileMode) pidFileFlags
221
  setLock fd (WriteLock, AbsoluteSeek, 0, 0)
222
  my_pid <- getProcessID
223
  _ <- fdWrite fd (show my_pid ++ "\n")
224
  return fd
225

    
226
-- | Helper function to ensure a socket doesn't exist. Should only be
227
-- called once we have locked the pid file successfully.
228
cleanupSocket :: FilePath -> IO ()
229
cleanupSocket socketPath =
230
  catchJust (guard . isDoesNotExistError) (removeLink socketPath)
231
            (const $ return ())
232

    
233
-- | Sets up a daemon's environment.
234
setupDaemonEnv :: FilePath -> FileMode -> IO ()
235
setupDaemonEnv cwd umask = do
236
  changeWorkingDirectory cwd
237
  _ <- setFileCreationMask umask
238
  _ <- createSession
239
  return ()
240

    
241
-- | Cleanup function, performing all the operations that need to be done prior
242
-- to shutting down a daemon.
243
finalCleanup :: FilePath -> IO ()
244
finalCleanup = removeFile
245

    
246
-- | Signal handler for the termination signal.
247
handleSigTerm :: ThreadId -> IO ()
248
handleSigTerm mainTID =
249
  -- Throw termination exception to the main thread, so that the daemon is
250
  -- actually stopped in the proper way, executing all the functions waiting on
251
  -- "finally" statement.
252
  Control.Exception.throwTo mainTID ExitSuccess
253

    
254
-- | Signal handler for reopening log files.
255
handleSigHup :: FilePath -> IO ()
256
handleSigHup path = do
257
  setupDaemonFDs (Just path)
258
  logInfo "Reopening log files after receiving SIGHUP"
259

    
260
-- | Sets up a daemon's standard file descriptors.
261
setupDaemonFDs :: Maybe FilePath -> IO ()
262
setupDaemonFDs logfile = do
263
  null_in_handle <- openFile devNull ReadMode
264
  null_out_handle <- openFile (fromMaybe devNull logfile) AppendMode
265
  hDuplicateTo null_in_handle stdin
266
  hDuplicateTo null_out_handle stdout
267
  hDuplicateTo null_out_handle stderr
268
  hClose null_in_handle
269
  hClose null_out_handle
270

    
271
-- | Computes the default bind address for a given family.
272
defaultBindAddr :: Int                  -- ^ The port we want
273
                -> Socket.Family        -- ^ The cluster IP family
274
                -> Result (Socket.Family, Socket.SockAddr)
275
defaultBindAddr port Socket.AF_INET =
276
  Ok (Socket.AF_INET,
277
      Socket.SockAddrInet (fromIntegral port) Socket.iNADDR_ANY)
278
defaultBindAddr port Socket.AF_INET6 =
279
  Ok (Socket.AF_INET6,
280
      Socket.SockAddrInet6 (fromIntegral port) 0 Socket.iN6ADDR_ANY 0)
281
defaultBindAddr _ fam = Bad $ "Unsupported address family: " ++ show fam
282

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

    
297
-- | Environment variable to override the assumed host name of the
298
-- current node.
299
vClusterHostNameEnvVar :: String
300
vClusterHostNameEnvVar = "GANETI_HOSTNAME"
301

    
302
getFQDN :: IO String
303
getFQDN = do
304
  hostname <- getHostName
305
  addrInfos <- Socket.getAddrInfo Nothing (Just hostname) Nothing
306
  let address = listToMaybe addrInfos >>= (Just . Socket.addrAddress)
307
  case address of
308
    Just a -> do
309
      fqdn <- liftM fst $ Socket.getNameInfo [] True False a
310
      return (fromMaybe hostname fqdn)
311
    Nothing -> return hostname
312

    
313
-- | Returns if the current node is the master node.
314
isMaster :: IO Bool
315
isMaster = do
316
  let ioErrorToNothing :: IOError -> IO (Maybe String)
317
      ioErrorToNothing _ = return Nothing
318
  vcluster_node <- Control.Exception.catch
319
                     (liftM Just (getEnv vClusterHostNameEnvVar))
320
                     ioErrorToNothing
321
  curNode <- case vcluster_node of
322
    Just node_name -> return node_name
323
    Nothing -> getFQDN
324
  masterNode <- Ssconf.getMasterNode Nothing
325
  case masterNode of
326
    Ok n -> return (curNode == n)
327
    Bad _ -> return False
328

    
329
-- | Ensures that the daemon runs on the right node (and exits
330
-- gracefully if it doesnt)
331
ensureNode :: GanetiDaemon -> IO ()
332
ensureNode daemon = do
333
  is_master <- isMaster
334
  when (daemonOnlyOnMaster daemon && not is_master) $ do
335
    putStrLn "Not master, exiting."
336
    exitWith (ExitFailure C.exitNotmaster)
337

    
338
-- | Run an I\/O action that might throw an I\/O error, under a
339
-- handler that will simply annotate and re-throw the exception.
340
describeError :: String -> Maybe Handle -> Maybe FilePath -> IO a -> IO a
341
describeError descr hndl fpath =
342
  modifyIOError (\e -> annotateIOError e descr hndl fpath)
343

    
344
-- | Run an I\/O action as a daemon.
345
--
346
-- WARNING: this only works in single-threaded mode (either using the
347
-- single-threaded runtime, or using the multi-threaded one but with
348
-- only one OS thread, i.e. -N1).
349
daemonize :: FilePath -> (Maybe Fd -> IO ()) -> IO ()
350
daemonize logfile action = do
351
  (rpipe, wpipe) <- createPipe
352
  -- first fork
353
  _ <- forkProcess $ do
354
    -- in the child
355
    closeFd rpipe
356
    let wpipe' = Just wpipe
357
    setupDaemonEnv "/" (unionFileModes groupModes otherModes)
358
    setupDaemonFDs (Just logfile) `Control.Exception.catch`
359
      handlePrepErr False wpipe'
360
    _ <- installHandler lostConnection (Catch (handleSigHup logfile)) Nothing
361
    -- second fork, launches the actual child code; standard
362
    -- double-fork technique
363
    _ <- forkProcess (action wpipe')
364
    exitImmediately ExitSuccess
365
  closeFd wpipe
366
  hndl <- fdToHandle rpipe
367
  errors <- hGetContents hndl
368
  ecode <- if null errors
369
             then return ExitSuccess
370
             else do
371
               hPutStrLn stderr $ daemonStartupErr errors
372
               return $ ExitFailure C.exitFailure
373
  exitImmediately ecode
374

    
375
-- | Generic daemon startup.
376
genericMain :: GanetiDaemon -- ^ The daemon we're running
377
            -> [OptType]    -- ^ The available options
378
            -> CheckFn a    -- ^ Check function
379
            -> PrepFn  a b  -- ^ Prepare function
380
            -> MainFn  a b  -- ^ Execution function
381
            -> IO ()
382
genericMain daemon options check_fn prep_fn exec_fn = do
383
  let progname = daemonName daemon
384

    
385
  (opts, args) <- parseArgs progname options
386

    
387
  -- Modify handleClient in Ganeti.UDSServer to remove this logging from luxid.
388
  when (optDebug opts && daemon == GanetiLuxid) .
389
    hPutStrLn stderr $
390
      printf C.debugModeConfidentialityWarning (daemonName daemon)
391

    
392
  ensureNode daemon
393

    
394
  exitUnless (null args) "This program doesn't take any arguments"
395

    
396
  unless (optNoUserChecks opts) $ do
397
    runtimeEnts <- getEnts
398
    ents <- exitIfBad "Can't find required user/groups" runtimeEnts
399
    verifyDaemonUser daemon ents
400

    
401
  syslog <- case optSyslogUsage opts of
402
              Nothing -> exitIfBad "Invalid cluster syslog setting" $
403
                         syslogUsageFromRaw C.syslogUsage
404
              Just v -> return v
405

    
406
  log_file <- daemonLogFile daemon
407
  -- run the check function and optionally exit if it returns an exit code
408
  check_result <- check_fn opts
409
  check_result' <- case check_result of
410
                     Left code -> exitWith code
411
                     Right v -> return v
412

    
413
  let processFn = if optDaemonize opts
414
                    then daemonize log_file
415
                    else \action -> action Nothing
416
  processFn $ innerMain daemon opts syslog check_result' prep_fn exec_fn
417

    
418
-- | Full prepare function.
419
--
420
-- This is executed after daemonization, and sets up both the log
421
-- files (a generic functionality) and the custom prepare function of
422
-- the daemon.
423
fullPrep :: GanetiDaemon  -- ^ The daemon we're running
424
         -> DaemonOptions -- ^ The options structure, filled from the cmdline
425
         -> SyslogUsage   -- ^ Syslog mode
426
         -> a             -- ^ Check results
427
         -> PrepFn a b    -- ^ Prepare function
428
         -> IO (FilePath, b)
429
fullPrep daemon opts syslog check_result prep_fn = do
430
  logfile <- if optDaemonize opts
431
               then return Nothing
432
               else liftM Just $ daemonLogFile daemon
433
  pidfile <- daemonPidFile daemon
434
  let dname = daemonName daemon
435
  setupLogging logfile dname (optDebug opts) True False syslog
436
  _ <- describeError "writing PID file; already locked?"
437
         Nothing (Just pidfile) $ writePidFile pidfile
438
  logNotice $ dname ++ " daemon startup"
439
  prep_res <- prep_fn opts check_result
440
  tid <- myThreadId
441
  _ <- installHandler sigTERM (Catch $ handleSigTerm tid) Nothing
442
  return (pidfile, prep_res)
443

    
444
-- | Inner daemon function.
445
--
446
-- This is executed after daemonization.
447
innerMain :: GanetiDaemon  -- ^ The daemon we're running
448
          -> DaemonOptions -- ^ The options structure, filled from the cmdline
449
          -> SyslogUsage   -- ^ Syslog mode
450
          -> a             -- ^ Check results
451
          -> PrepFn a b    -- ^ Prepare function
452
          -> MainFn a b    -- ^ Execution function
453
          -> Maybe Fd      -- ^ Error reporting function
454
          -> IO ()
455
innerMain daemon opts syslog check_result prep_fn exec_fn fd = do
456
  (pidFile, prep_result) <- fullPrep daemon opts syslog check_result prep_fn
457
                 `Control.Exception.catch` handlePrepErr True fd
458
  -- no error reported, we should now close the fd
459
  maybeCloseFd fd
460
  finally (exec_fn opts check_result prep_result) (finalCleanup pidFile)
461

    
462
-- | Daemon prepare error handling function.
463
handlePrepErr :: Bool -> Maybe Fd -> IOError -> IO a
464
handlePrepErr logging_setup fd err = do
465
  let msg = show err
466
  case fd of
467
    -- explicitly writing to the fd directly, since when forking it's
468
    -- better (safer) than trying to convert this into a full handle
469
    Just fd' -> fdWrite fd' msg >> return ()
470
    Nothing  -> hPutStrLn stderr (daemonStartupErr msg)
471
  when logging_setup $ logError msg
472
  exitWith $ ExitFailure 1
473

    
474
-- | Close a file descriptor.
475
maybeCloseFd :: Maybe Fd -> IO ()
476
maybeCloseFd Nothing   = return ()
477
maybeCloseFd (Just fd) = closeFd fd