Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Daemon.hs @ 1251817b

History | View | Annotate | Download (12 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
  , writePidFile
41
  , genericMain
42
  ) where
43

    
44
import Control.Exception
45
import Control.Monad
46
import Data.Maybe (fromMaybe)
47
import qualified Data.Version
48
import Data.Word
49
import GHC.IO.Handle (hDuplicateTo)
50
import qualified Network.Socket as Socket
51
import System.Console.GetOpt
52
import System.Exit
53
import System.Environment
54
import System.Info
55
import System.IO
56
import System.Posix.Directory
57
import System.Posix.Files
58
import System.Posix.IO
59
import System.Posix.Process
60
import System.Posix.Types
61
import System.Posix.Signals
62
import Text.Printf
63

    
64
import Ganeti.Logging
65
import Ganeti.Runtime
66
import Ganeti.BasicTypes
67
import Ganeti.HTools.Utils
68
import qualified Ganeti.HTools.Version as Version(version)
69
import qualified Ganeti.Constants as C
70
import qualified Ganeti.Ssconf as Ssconf
71

    
72
-- * Constants
73

    
74
-- | \/dev\/null path.
75
devNull :: FilePath
76
devNull = "/dev/null"
77

    
78
-- * Data types
79

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

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

    
105
-- | Abrreviation for the option type.
106
type OptType = OptDescr (DaemonOptions -> Result DaemonOptions)
107

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

    
119
-- * Command line options
120

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

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

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

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

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

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

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

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

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

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

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

    
198
-- * Daemon-related functions
199
-- | PID file mode.
200
pidFileMode :: FileMode
201
pidFileMode = unionFileModes ownerReadMode ownerWriteMode
202

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

    
212
-- | Helper to format an IOError.
213
formatIOError :: String -> IOError -> String
214
formatIOError msg err = msg ++ ": " ++  show err
215

    
216
-- | Wrapper over '_writePidFile' that transforms IO exceptions into a
217
-- 'Bad' value.
218
writePidFile :: FilePath -> IO (Result Fd)
219
writePidFile path = do
220
  Control.Exception.catch
221
    (fmap Ok $ _writePidFile path)
222
    (return . Bad . formatIOError "Failure during writing of the pid file")
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
  ainfo <- case optBindAddress opts of
284
             Nothing -> return (def_family >>= defaultBindAddr port)
285
             Just saddr -> Control.Exception.catch
286
                             (resolveAddr port saddr)
287
                             (annotateIOError $ "Invalid address " ++ saddr)
288
  return ainfo
289

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

    
310
-- | Generic daemon startup.
311
genericMain :: GanetiDaemon -> [OptType] -> (DaemonOptions -> IO ()) -> IO ()
312
genericMain daemon options main = do
313
  let progname = daemonName daemon
314
  (opts, args) <- parseArgs progname options
315

    
316
  when (optShowHelp opts) $ do
317
    putStr $ usageHelp progname options
318
    exitWith ExitSuccess
319
  when (optShowVer opts) $ do
320
    printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
321
           progname Version.version
322
           compilerName (Data.Version.showVersion compilerVersion)
323
           os arch :: IO ()
324
    exitWith ExitSuccess
325

    
326
  exitUnless (null args) "This program doesn't take any arguments"
327

    
328
  unless (optNoUserChecks opts) $ do
329
    runtimeEnts <- getEnts
330
    ents <- exitIfBad "Can't find required user/groups" runtimeEnts
331
    verifyDaemonUser daemon ents
332

    
333
  syslog <- case optSyslogUsage opts of
334
              Nothing -> exitIfBad "Invalid cluster syslog setting" $
335
                         syslogUsageFromRaw C.syslogUsage
336
              Just v -> return v
337
  let processFn = if optDaemonize opts
338
                    then daemonize (daemonLogFile daemon)
339
                    else id
340
  processFn $ innerMain daemon opts syslog (main opts)
341

    
342
-- | Inner daemon function.
343
--
344
-- This is executed after daemonization.
345
innerMain :: GanetiDaemon -> DaemonOptions -> SyslogUsage -> IO () -> IO ()
346
innerMain daemon opts syslog main = do
347
  let logfile = if optDaemonize opts
348
                  then Nothing
349
                  else Just $ daemonLogFile daemon
350
  setupLogging logfile (daemonName daemon) (optDebug opts) True False syslog
351
  pid_fd <- writePidFile (daemonPidFile daemon)
352
  _ <- exitIfBad "Cannot write PID file; already locked? Error" pid_fd
353
  logNotice "starting"
354
  main