Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Daemon.hs @ 2997cb0a

History | View | Annotate | Download (12.3 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
  , defaultOptions
30
  , oShowHelp
31
  , oShowVer
32
  , oNoDaemonize
33
  , oNoUserChecks
34
  , oDebug
35
  , oPort
36
  , oBindAddress
37
  , oSyslogUsage
38
  , parseArgs
39
  , parseAddress
40
  , cleanupSocket
41
  , writePidFile
42
  , genericMain
43
  ) where
44

    
45
import Control.Exception
46
import Control.Monad
47
import Data.Maybe (fromMaybe)
48
import qualified Data.Version
49
import Data.Word
50
import GHC.IO.Handle (hDuplicateTo)
51
import qualified Network.Socket as Socket
52
import Prelude hiding (catch)
53
import System.Console.GetOpt
54
import System.Exit
55
import System.Environment
56
import System.Info
57
import System.IO
58
import System.IO.Error (isDoesNotExistError)
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
import Text.Printf
66

    
67
import Ganeti.Logging
68
import Ganeti.Runtime
69
import Ganeti.BasicTypes
70
import Ganeti.HTools.Utils
71
import qualified Ganeti.Version as Version (version)
72
import qualified Ganeti.Constants as C
73
import qualified Ganeti.Ssconf as Ssconf
74

    
75
-- * Constants
76

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

    
81
-- * Data types
82

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

    
95
-- | Default values for the command line options.
96
defaultOptions :: DaemonOptions
97
defaultOptions  = DaemonOptions
98
  { optShowHelp     = False
99
  , optShowVer      = False
100
  , optDaemonize    = True
101
  , optPort         = Nothing
102
  , optDebug        = False
103
  , optNoUserChecks = False
104
  , optBindAddress  = Nothing
105
  , optSyslogUsage  = Nothing
106
  }
107

    
108
-- | Abrreviation for the option type.
109
type OptType = OptDescr (DaemonOptions -> Result DaemonOptions)
110

    
111
-- | Helper function for required arguments which need to be converted
112
-- as opposed to stored just as string.
113
reqWithConversion :: (String -> Result a)
114
                  -> (a -> DaemonOptions -> Result DaemonOptions)
115
                  -> String
116
                  -> ArgDescr (DaemonOptions -> Result DaemonOptions)
117
reqWithConversion conversion_fn updater_fn metavar =
118
  ReqArg (\string_opt opts -> do
119
            parsed_value <- conversion_fn string_opt
120
            updater_fn parsed_value opts) metavar
121

    
122
-- * Command line options
123

    
124
oShowHelp :: OptType
125
oShowHelp = Option "h" ["help"]
126
            (NoArg (\ opts -> Ok opts { optShowHelp = True}))
127
            "Show the help message and exit"
128

    
129
oShowVer :: OptType
130
oShowVer = Option "V" ["version"]
131
           (NoArg (\ opts -> Ok opts { optShowVer = True}))
132
           "Show the version of the program and exit"
133

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

    
139
oDebug :: OptType
140
oDebug = Option "d" ["debug"]
141
         (NoArg (\ opts -> Ok opts { optDebug = True }))
142
         "Enable debug messages"
143

    
144
oNoUserChecks :: OptType
145
oNoUserChecks = Option "" ["no-user-checks"]
146
         (NoArg (\ opts -> Ok opts { optNoUserChecks = True }))
147
         "Ignore user checks"
148

    
149
oPort :: Int -> OptType
150
oPort def = Option "p" ["port"]
151
            (reqWithConversion (tryRead "reading port")
152
             (\port opts -> Ok opts { optPort = Just port }) "PORT")
153
            ("Network port (default: " ++ show def ++ ")")
154

    
155
oBindAddress :: OptType
156
oBindAddress = Option "b" ["bind"]
157
               (ReqArg (\addr opts -> Ok opts { optBindAddress = Just addr })
158
                "ADDR")
159
               "Bind address (default depends on cluster configuration)"
160

    
161
oSyslogUsage :: OptType
162
oSyslogUsage = Option "" ["syslog"]
163
               (reqWithConversion syslogUsageFromRaw
164
                (\su opts -> Ok opts { optSyslogUsage = Just su })
165
                "SYSLOG")
166
               ("Enable logging to syslog (except debug \
167
                \messages); one of 'no', 'yes' or 'only' [" ++ C.syslogUsage ++
168
                "]")
169

    
170
-- | Usage info.
171
usageHelp :: String -> [OptType] -> String
172
usageHelp progname =
173
  usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
174
             progname Version.version progname)
175

    
176
-- | Command line parser, using the 'Options' structure.
177
parseOpts :: [String]               -- ^ The command line arguments
178
          -> String                 -- ^ The program name
179
          -> [OptType]              -- ^ The supported command line options
180
          -> IO (DaemonOptions, [String]) -- ^ The resulting options
181
                                          -- and leftover arguments
182
parseOpts argv progname options =
183
  case getOpt Permute options argv of
184
    (opt_list, args, []) ->
185
      do
186
        parsed_opts <-
187
          exitIfBad "Error while parsing command line arguments" $
188
          foldM (flip id) defaultOptions opt_list
189
        return (parsed_opts, args)
190
    (_, _, errs) -> do
191
      hPutStrLn stderr $ "Command line error: "  ++ concat errs
192
      hPutStrLn stderr $ usageHelp progname options
193
      exitWith $ ExitFailure 2
194

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

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

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

    
215
-- | Helper to format an IOError.
216
formatIOError :: String -> IOError -> String
217
formatIOError msg err = msg ++ ": " ++  show err
218

    
219
-- | Wrapper over '_writePidFile' that transforms IO exceptions into a
220
-- 'Bad' value.
221
writePidFile :: FilePath -> IO (Result Fd)
222
writePidFile path = do
223
  catch (fmap Ok $ _writePidFile path)
224
    (return . Bad . formatIOError "Failure during writing of the pid file")
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 = do
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
-- | Signal handler for reopening log files.
242
handleSigHup :: FilePath -> IO ()
243
handleSigHup path = do
244
  setupDaemonFDs (Just path)
245
  logInfo "Reopening log files after receiving SIGHUP"
246

    
247
-- | Sets up a daemon's standard file descriptors.
248
setupDaemonFDs :: Maybe FilePath -> IO ()
249
setupDaemonFDs logfile = do
250
  null_in_handle <- openFile devNull ReadMode
251
  null_out_handle <- openFile (fromMaybe devNull logfile) AppendMode
252
  hDuplicateTo null_in_handle stdin
253
  hDuplicateTo null_out_handle stdout
254
  hDuplicateTo null_out_handle stderr
255
  hClose null_in_handle
256
  hClose null_out_handle
257

    
258
-- | Computes the default bind address for a given family.
259
defaultBindAddr :: Int                  -- ^ The port we want
260
                -> Socket.Family        -- ^ The cluster IP family
261
                -> Result (Socket.Family, Socket.SockAddr)
262
defaultBindAddr port Socket.AF_INET =
263
  Ok $ (Socket.AF_INET,
264
        Socket.SockAddrInet (fromIntegral port) Socket.iNADDR_ANY)
265
defaultBindAddr port Socket.AF_INET6 =
266
  Ok $ (Socket.AF_INET6,
267
        Socket.SockAddrInet6 (fromIntegral port) 0 Socket.iN6ADDR_ANY 0)
268
defaultBindAddr _ fam = Bad $ "Unsupported address family: " ++ show fam
269

    
270
-- | Default hints for the resolver
271
resolveAddrHints :: Maybe Socket.AddrInfo
272
resolveAddrHints =
273
  Just Socket.defaultHints { Socket.addrFlags = [Socket.AI_NUMERICHOST,
274
                                                 Socket.AI_NUMERICSERV] }
275

    
276
-- | Resolves a numeric address.
277
resolveAddr :: Int -> String -> IO (Result (Socket.Family, Socket.SockAddr))
278
resolveAddr port str = do
279
  resolved <- Socket.getAddrInfo resolveAddrHints (Just str) (Just (show port))
280
  return $ case resolved of
281
             [] -> Bad "Invalid results from lookup?"
282
             best:_ -> Ok $ (Socket.addrFamily best, Socket.addrAddress best)
283

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

    
298
-- | Run an I/O action as a daemon.
299
--
300
-- WARNING: this only works in single-threaded mode (either using the
301
-- single-threaded runtime, or using the multi-threaded one but with
302
-- only one OS thread, i.e. -N1).
303
--
304
-- FIXME: this doesn't support error reporting and the prepfn
305
-- functionality.
306
daemonize :: FilePath -> IO () -> IO ()
307
daemonize logfile action = do
308
  -- first fork
309
  _ <- forkProcess $ do
310
    -- in the child
311
    setupDaemonEnv "/" (unionFileModes groupModes otherModes)
312
    setupDaemonFDs $ Just logfile
313
    _ <- installHandler lostConnection (Catch (handleSigHup logfile)) Nothing
314
    _ <- forkProcess action
315
    exitImmediately ExitSuccess
316
  exitImmediately ExitSuccess
317

    
318
-- | Generic daemon startup.
319
genericMain :: GanetiDaemon -> [OptType] -> (DaemonOptions -> IO ()) -> IO ()
320
genericMain daemon options main = do
321
  let progname = daemonName daemon
322
  (opts, args) <- parseArgs progname options
323

    
324
  when (optShowHelp opts) $ do
325
    putStr $ usageHelp progname options
326
    exitSuccess
327
  when (optShowVer opts) $ do
328
    printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
329
           progname Version.version
330
           compilerName (Data.Version.showVersion compilerVersion)
331
           os arch :: IO ()
332
    exitSuccess
333

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

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

    
341
  syslog <- case optSyslogUsage opts of
342
              Nothing -> exitIfBad "Invalid cluster syslog setting" $
343
                         syslogUsageFromRaw C.syslogUsage
344
              Just v -> return v
345
  let processFn = if optDaemonize opts
346
                    then daemonize (daemonLogFile daemon)
347
                    else id
348
  processFn $ innerMain daemon opts syslog (main opts)
349

    
350
-- | Inner daemon function.
351
--
352
-- This is executed after daemonization.
353
innerMain :: GanetiDaemon -> DaemonOptions -> SyslogUsage -> IO () -> IO ()
354
innerMain daemon opts syslog main = do
355
  let logfile = if optDaemonize opts
356
                  then Nothing
357
                  else Just $ daemonLogFile daemon
358
  setupLogging logfile (daemonName daemon) (optDebug opts) True False syslog
359
  pid_fd <- writePidFile (daemonPidFile daemon)
360
  _ <- exitIfBad "Cannot write PID file; already locked? Error" pid_fd
361
  logNotice "starting"
362
  main