Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Daemon.hs @ a4c0fe1e

History | View | Annotate | Download (12.2 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

    
200
-- | PID file mode.
201
pidFileMode :: FileMode
202
pidFileMode = unionFileModes ownerReadMode ownerWriteMode
203

    
204
-- | PID file open flags.
205
pidFileFlags :: OpenFileFlags
206
pidFileFlags = defaultFileFlags { noctty = True, trunc = False }
207

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

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

    
221
-- | Wrapper over '_writePidFile' that transforms IO exceptions into a
222
-- 'Bad' value.
223
writePidFile :: FilePath -> IO (Result Fd)
224
writePidFile path = do
225
  Control.Exception.catch
226
    (fmap Ok $ _writePidFile path)
227
    (return . Bad . formatIOError "Failure during writing of the pid file")
228

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

    
237
-- | Signal handler for reopening log files.
238
handleSigHup :: FilePath -> IO ()
239
handleSigHup path = do
240
  setupDaemonFDs (Just path)
241
  logInfo "Reopening log files after receiving SIGHUP"
242

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

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

    
266
-- | Default hints for the resolver
267
resolveAddrHints :: Maybe Socket.AddrInfo
268
resolveAddrHints =
269
  Just Socket.defaultHints { Socket.addrFlags = [Socket.AI_NUMERICHOST,
270
                                                 Socket.AI_NUMERICSERV] }
271

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

    
280
-- | Based on the options, compute the socket address to use for the
281
-- daemon.
282
parseAddress :: DaemonOptions      -- ^ Command line options
283
             -> Int                -- ^ Default port for this daemon
284
             -> IO (Result (Socket.Family, Socket.SockAddr))
285
parseAddress opts defport = do
286
  let port = maybe defport fromIntegral $ optPort opts
287
  def_family <- Ssconf.getPrimaryIPFamily Nothing
288
  ainfo <- case optBindAddress opts of
289
             Nothing -> return (def_family >>= defaultBindAddr port)
290
             Just saddr -> Control.Exception.catch
291
                             (resolveAddr port saddr)
292
                             (annotateIOError $ "Invalid address " ++ saddr)
293
  return ainfo
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
--
301
-- FIXME: this doesn't support error reporting and the prepfn
302
-- functionality.
303
daemonize :: FilePath -> IO () -> IO ()
304
daemonize logfile action = do
305
  -- first fork
306
  _ <- forkProcess $ do
307
    -- in the child
308
    setupDaemonEnv "/" (unionFileModes groupModes otherModes)
309
    setupDaemonFDs $ Just logfile
310
    _ <- installHandler lostConnection (Catch (handleSigHup logfile)) Nothing
311
    _ <- forkProcess action
312
    exitImmediately ExitSuccess
313
  exitImmediately ExitSuccess
314

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

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

    
331
  exitUnless (null args) "This program doesn't take any arguments"
332

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

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

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