Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Daemon.hs @ b714ff89

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

    
44
import Control.Monad
45
import qualified Data.Version
46
import Data.Word
47
import qualified Network.Socket as Socket
48
import System.Console.GetOpt
49
import System.Exit
50
import System.Environment
51
import System.Info
52
import System.IO
53
import System.Posix.Directory
54
import System.Posix.Files
55
import System.Posix.IO
56
import System.Posix.Process
57
import System.Posix.Types
58
import Text.Printf
59

    
60
import Ganeti.Logging
61
import Ganeti.Runtime
62
import Ganeti.BasicTypes
63
import Ganeti.HTools.Utils
64
import qualified Ganeti.HTools.Version as Version(version)
65
import qualified Ganeti.Constants as C
66
import qualified Ganeti.Ssconf as Ssconf
67

    
68
-- * Data types
69

    
70
-- | Command line options structure.
71
data DaemonOptions = DaemonOptions
72
  { optShowHelp     :: Bool           -- ^ Just show the help
73
  , optShowVer      :: Bool           -- ^ Just show the program version
74
  , optDaemonize    :: Bool           -- ^ Whether to daemonize or not
75
  , optPort         :: Maybe Word16   -- ^ Override for the network port
76
  , optDebug        :: Bool           -- ^ Enable debug messages
77
  , optNoUserChecks :: Bool           -- ^ Ignore user checks
78
  , optBindAddress  :: Maybe String   -- ^ Override for the bind address
79
  , optSyslogUsage  :: Maybe SyslogUsage -- ^ Override for Syslog usage
80
  }
81

    
82
-- | Default values for the command line options.
83
defaultOptions :: DaemonOptions
84
defaultOptions  = DaemonOptions
85
  { optShowHelp     = False
86
  , optShowVer      = False
87
  , optDaemonize    = True
88
  , optPort         = Nothing
89
  , optDebug        = False
90
  , optNoUserChecks = False
91
  , optBindAddress  = Nothing
92
  , optSyslogUsage  = Nothing
93
  }
94

    
95
-- | Abrreviation for the option type.
96
type OptType = OptDescr (DaemonOptions -> Result DaemonOptions)
97

    
98
-- | Helper function for required arguments which need to be converted
99
-- as opposed to stored just as string.
100
reqWithConversion :: (String -> Result a)
101
                  -> (a -> DaemonOptions -> Result DaemonOptions)
102
                  -> String
103
                  -> ArgDescr (DaemonOptions -> Result DaemonOptions)
104
reqWithConversion conversion_fn updater_fn metavar =
105
  ReqArg (\string_opt opts -> do
106
            parsed_value <- conversion_fn string_opt
107
            updater_fn parsed_value opts) metavar
108

    
109
-- * Command line options
110

    
111
oShowHelp :: OptType
112
oShowHelp = Option "h" ["help"]
113
            (NoArg (\ opts -> Ok opts { optShowHelp = True}))
114
            "Show the help message and exit"
115

    
116
oShowVer :: OptType
117
oShowVer = Option "V" ["version"]
118
           (NoArg (\ opts -> Ok opts { optShowVer = True}))
119
           "Show the version of the program and exit"
120

    
121
oNoDaemonize :: OptType
122
oNoDaemonize = Option "f" ["foreground"]
123
               (NoArg (\ opts -> Ok opts { optDaemonize = False}))
124
               "Don't detach from the current terminal"
125

    
126
oDebug :: OptType
127
oDebug = Option "d" ["debug"]
128
         (NoArg (\ opts -> Ok opts { optDebug = True }))
129
         "Enable debug messages"
130

    
131
oNoUserChecks :: OptType
132
oNoUserChecks = Option "" ["no-user-checks"]
133
         (NoArg (\ opts -> Ok opts { optNoUserChecks = True }))
134
         "Ignore user checks"
135

    
136
oPort :: Int -> OptType
137
oPort def = Option "p" ["port"]
138
            (reqWithConversion (tryRead "reading port")
139
             (\port opts -> Ok opts { optPort = Just port }) "PORT")
140
            ("Network port (default: " ++ show def ++ ")")
141

    
142
oBindAddress :: OptType
143
oBindAddress = Option "b" ["bind"]
144
               (ReqArg (\addr opts -> Ok opts { optBindAddress = Just addr })
145
                "ADDR")
146
               "Bind address (default depends on cluster configuration)"
147

    
148
oSyslogUsage :: OptType
149
oSyslogUsage = Option "" ["syslog"]
150
               (reqWithConversion syslogUsageFromRaw
151
                (\su opts -> Ok opts { optSyslogUsage = Just su })
152
                "SYSLOG")
153
               ("Enable logging to syslog (except debug \
154
                \messages); one of 'no', 'yes' or 'only' [" ++ C.syslogUsage ++
155
                "]")
156

    
157
-- | Usage info.
158
usageHelp :: String -> [OptType] -> String
159
usageHelp progname =
160
  usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
161
             progname Version.version progname)
162

    
163
-- | Command line parser, using the 'Options' structure.
164
parseOpts :: [String]               -- ^ The command line arguments
165
          -> String                 -- ^ The program name
166
          -> [OptType]              -- ^ The supported command line options
167
          -> IO (DaemonOptions, [String]) -- ^ The resulting options
168
                                          -- and leftover arguments
169
parseOpts argv progname options =
170
  case getOpt Permute options argv of
171
    (opt_list, args, []) ->
172
      do
173
        parsed_opts <-
174
          case foldM (flip id) defaultOptions opt_list of
175
            Bad msg -> do
176
              hPutStrLn stderr "Error while parsing command\
177
                               \line arguments:"
178
              hPutStrLn stderr msg
179
              exitWith $ ExitFailure 1
180
            Ok val -> return val
181
        return (parsed_opts, args)
182
    (_, _, errs) -> do
183
      hPutStrLn stderr $ "Command line error: "  ++ concat errs
184
      hPutStrLn stderr $ usageHelp progname options
185
      exitWith $ ExitFailure 2
186

    
187
-- | Small wrapper over getArgs and 'parseOpts'.
188
parseArgs :: String -> [OptType] -> IO (DaemonOptions, [String])
189
parseArgs cmd options = do
190
  cmd_args <- getArgs
191
  parseOpts cmd_args cmd options
192

    
193
-- * Daemon-related functions
194
-- | PID file mode.
195
pidFileMode :: FileMode
196
pidFileMode = unionFileModes ownerReadMode ownerWriteMode
197

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

    
207
-- | Wrapper over '_writePidFile' that transforms IO exceptions into a
208
-- 'Bad' value.
209
writePidFile :: FilePath -> IO (Result Fd)
210
writePidFile path = do
211
  catch (fmap Ok $ _writePidFile path) (return . Bad . show)
212

    
213
-- | Sets up a daemon's environment.
214
setupDaemonEnv :: FilePath -> FileMode -> IO ()
215
setupDaemonEnv cwd umask = do
216
  changeWorkingDirectory cwd
217
  _ <- setFileCreationMask umask
218
  _ <- createSession
219
  return ()
220

    
221
-- | Computes the default bind address for a given family.
222
defaultBindAddr :: Int                  -- ^ The port we want
223
                -> Socket.Family        -- ^ The cluster IP family
224
                -> Result (Socket.Family, Socket.SockAddr)
225
defaultBindAddr port Socket.AF_INET =
226
  Ok $ (Socket.AF_INET,
227
        Socket.SockAddrInet (fromIntegral port) Socket.iNADDR_ANY)
228
defaultBindAddr port Socket.AF_INET6 =
229
  Ok $ (Socket.AF_INET6,
230
        Socket.SockAddrInet6 (fromIntegral port) 0 Socket.iN6ADDR_ANY 0)
231
defaultBindAddr _ fam = Bad $ "Unsupported address family: " ++ show fam
232

    
233
-- | Default hints for the resolver
234
resolveAddrHints :: Maybe Socket.AddrInfo
235
resolveAddrHints =
236
  Just Socket.defaultHints { Socket.addrFlags = [Socket.AI_NUMERICHOST,
237
                                                 Socket.AI_NUMERICSERV] }
238

    
239
-- | Resolves a numeric address.
240
resolveAddr :: Int -> String -> IO (Result (Socket.Family, Socket.SockAddr))
241
resolveAddr port str = do
242
  resolved <- Socket.getAddrInfo resolveAddrHints (Just str) (Just (show port))
243
  return $ case resolved of
244
             [] -> Bad "Invalid results from lookup?"
245
             best:_ -> Ok $ (Socket.addrFamily best, Socket.addrAddress best)
246

    
247
-- | Based on the options, compute the socket address to use for the
248
-- daemon.
249
parseAddress :: DaemonOptions      -- ^ Command line options
250
             -> Int                -- ^ Default port for this daemon
251
             -> IO (Result (Socket.Family, Socket.SockAddr))
252
parseAddress opts defport = do
253
  let port = maybe defport fromIntegral $ optPort opts
254
  def_family <- Ssconf.getPrimaryIPFamily Nothing
255
  ainfo <- case optBindAddress opts of
256
             Nothing -> return (def_family >>= defaultBindAddr port)
257
             Just saddr -> catch (resolveAddr port saddr)
258
                           (annotateIOError $ "Invalid address " ++ saddr)
259
  return ainfo
260

    
261
-- | Run an I/O action as a daemon.
262
--
263
-- WARNING: this only works in single-threaded mode (either using the
264
-- single-threaded runtime, or using the multi-threaded one but with
265
-- only one OS thread, i.e. -N1).
266
--
267
-- FIXME: this doesn't support error reporting and the prepfn
268
-- functionality.
269
daemonize :: IO () -> IO ()
270
daemonize action = do
271
  -- first fork
272
  _ <- forkProcess $ do
273
    -- in the child
274
    setupDaemonEnv "/" (unionFileModes groupModes otherModes)
275
    _ <- forkProcess action
276
    exitImmediately ExitSuccess
277
  exitImmediately ExitSuccess
278

    
279
-- | Generic daemon startup.
280
genericMain :: GanetiDaemon -> [OptType] -> (DaemonOptions -> IO ()) -> IO ()
281
genericMain daemon options main = do
282
  let progname = daemonName daemon
283
  (opts, args) <- parseArgs progname options
284

    
285
  when (optShowHelp opts) $ do
286
    putStr $ usageHelp progname options
287
    exitWith ExitSuccess
288
  when (optShowVer opts) $ do
289
    printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
290
           progname Version.version
291
           compilerName (Data.Version.showVersion compilerVersion)
292
           os arch :: IO ()
293
    exitWith ExitSuccess
294
  unless (null args) $ do
295
         hPutStrLn stderr "This program doesn't take any arguments"
296
         exitWith $ ExitFailure C.exitFailure
297

    
298
  unless (optNoUserChecks opts) $ do
299
    runtimeEnts <- getEnts
300
    case runtimeEnts of
301
      Bad msg -> do
302
        hPutStrLn stderr $ "Can't find required user/groups: " ++ msg
303
        exitWith $ ExitFailure C.exitFailure
304
      Ok ents -> verifyDaemonUser daemon ents
305

    
306
  syslog <- case optSyslogUsage opts of
307
              Nothing -> exitIfBad $
308
                         annotateResult "Invalid cluster syslog setting" $
309
                         syslogUsageFromRaw C.syslogUsage
310
              Just v -> return v
311
  let processFn = if optDaemonize opts then daemonize else id
312
  processFn $ innerMain daemon opts syslog (main opts)
313

    
314
-- | Inner daemon function.
315
--
316
-- This is executed after daemonization.
317
innerMain :: GanetiDaemon -> DaemonOptions -> SyslogUsage -> IO () -> IO ()
318
innerMain daemon opts syslog main = do
319
  setupLogging (daemonLogFile daemon) (daemonName daemon) (optDebug opts)
320
                 (not (optDaemonize opts)) False syslog
321
  pid_fd <- writePidFile (daemonPidFile daemon)
322
  case pid_fd of
323
    Bad msg -> do
324
         hPutStrLn stderr $ "Cannot write PID file; already locked? Error: " ++
325
                   msg
326
         exitWith $ ExitFailure 1
327
    _ -> return ()
328
  logNotice "starting"
329
  main