Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Daemon.hs @ ce207617

History | View | Annotate | Download (10.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 Data.Word
49
import GHC.IO.Handle (hDuplicateTo)
50
import qualified Network.Socket as Socket
51
import Prelude hiding (catch)
52
import System.Console.GetOpt
53
import System.Exit
54
import System.Environment
55
import System.IO
56
import System.IO.Error (isDoesNotExistError)
57
import System.Posix.Directory
58
import System.Posix.Files
59
import System.Posix.IO
60
import System.Posix.Process
61
import System.Posix.Types
62
import System.Posix.Signals
63

    
64
import Ganeti.Common as Common
65
import Ganeti.Logging
66
import Ganeti.Runtime
67
import Ganeti.BasicTypes
68
import Ganeti.HTools.Utils
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
instance StandardOptions DaemonOptions where
106
  helpRequested = optShowHelp
107
  verRequested  = optShowVer
108
  requestHelp o = o { optShowHelp = True }
109
  requestVer  o = o { optShowVer  = True }
110

    
111
-- | Abrreviation for the option type.
112
type OptType = GenericOptType DaemonOptions
113

    
114
-- * Command line options
115

    
116
oNoDaemonize :: OptType
117
oNoDaemonize =
118
  (Option "f" ["foreground"]
119
   (NoArg (\ opts -> Ok opts { optDaemonize = False}))
120
   "Don't detach from the current terminal",
121
   OptComplNone)
122

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

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

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

    
145
oBindAddress :: OptType
146
oBindAddress =
147
  (Option "b" ["bind"]
148
   (ReqArg (\addr opts -> Ok opts { optBindAddress = Just addr })
149
    "ADDR")
150
   "Bind address (default depends on cluster configuration)",
151
   OptComplInetAddr)
152

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

    
164
-- | Generic options.
165
genericOpts :: [OptType]
166
genericOpts = [ oShowHelp
167
              , oShowVer
168
              ]
169

    
170
-- | Small wrapper over getArgs and 'parseOpts'.
171
parseArgs :: String -> [OptType] -> IO (DaemonOptions, [String])
172
parseArgs cmd options = do
173
  cmd_args <- getArgs
174
  parseOpts defaultOptions cmd_args cmd $ options ++ genericOpts
175

    
176
-- * Daemon-related functions
177
-- | PID file mode.
178
pidFileMode :: FileMode
179
pidFileMode = unionFileModes ownerReadMode ownerWriteMode
180

    
181
-- | Writes a PID file and locks it.
182
_writePidFile :: FilePath -> IO Fd
183
_writePidFile path = do
184
  fd <- createFile path pidFileMode
185
  setLock fd (WriteLock, AbsoluteSeek, 0, 0)
186
  my_pid <- getProcessID
187
  _ <- fdWrite fd (show my_pid ++ "\n")
188
  return fd
189

    
190
-- | Helper to format an IOError.
191
formatIOError :: String -> IOError -> String
192
formatIOError msg err = msg ++ ": " ++  show err
193

    
194
-- | Wrapper over '_writePidFile' that transforms IO exceptions into a
195
-- 'Bad' value.
196
writePidFile :: FilePath -> IO (Result Fd)
197
writePidFile path =
198
  catch (fmap Ok $ _writePidFile path)
199
    (return . Bad . formatIOError "Failure during writing of the pid file")
200

    
201
-- | Helper function to ensure a socket doesn't exist. Should only be
202
-- called once we have locked the pid file successfully.
203
cleanupSocket :: FilePath -> IO ()
204
cleanupSocket socketPath =
205
  catchJust (guard . isDoesNotExistError) (removeLink socketPath)
206
            (const $ return ())
207

    
208
-- | Sets up a daemon's environment.
209
setupDaemonEnv :: FilePath -> FileMode -> IO ()
210
setupDaemonEnv cwd umask = do
211
  changeWorkingDirectory cwd
212
  _ <- setFileCreationMask umask
213
  _ <- createSession
214
  return ()
215

    
216
-- | Signal handler for reopening log files.
217
handleSigHup :: FilePath -> IO ()
218
handleSigHup path = do
219
  setupDaemonFDs (Just path)
220
  logInfo "Reopening log files after receiving SIGHUP"
221

    
222
-- | Sets up a daemon's standard file descriptors.
223
setupDaemonFDs :: Maybe FilePath -> IO ()
224
setupDaemonFDs logfile = do
225
  null_in_handle <- openFile devNull ReadMode
226
  null_out_handle <- openFile (fromMaybe devNull logfile) AppendMode
227
  hDuplicateTo null_in_handle stdin
228
  hDuplicateTo null_out_handle stdout
229
  hDuplicateTo null_out_handle stderr
230
  hClose null_in_handle
231
  hClose null_out_handle
232

    
233
-- | Computes the default bind address for a given family.
234
defaultBindAddr :: Int                  -- ^ The port we want
235
                -> Socket.Family        -- ^ The cluster IP family
236
                -> Result (Socket.Family, Socket.SockAddr)
237
defaultBindAddr port Socket.AF_INET =
238
  Ok (Socket.AF_INET,
239
      Socket.SockAddrInet (fromIntegral port) Socket.iNADDR_ANY)
240
defaultBindAddr port Socket.AF_INET6 =
241
  Ok (Socket.AF_INET6,
242
      Socket.SockAddrInet6 (fromIntegral port) 0 Socket.iN6ADDR_ANY 0)
243
defaultBindAddr _ fam = Bad $ "Unsupported address family: " ++ show fam
244

    
245
-- | Default hints for the resolver
246
resolveAddrHints :: Maybe Socket.AddrInfo
247
resolveAddrHints =
248
  Just Socket.defaultHints { Socket.addrFlags = [Socket.AI_NUMERICHOST,
249
                                                 Socket.AI_NUMERICSERV] }
250

    
251
-- | Resolves a numeric address.
252
resolveAddr :: Int -> String -> IO (Result (Socket.Family, Socket.SockAddr))
253
resolveAddr port str = do
254
  resolved <- Socket.getAddrInfo resolveAddrHints (Just str) (Just (show port))
255
  return $ case resolved of
256
             [] -> Bad "Invalid results from lookup?"
257
             best:_ -> Ok (Socket.addrFamily best, Socket.addrAddress best)
258

    
259
-- | Based on the options, compute the socket address to use for the
260
-- daemon.
261
parseAddress :: DaemonOptions      -- ^ Command line options
262
             -> Int                -- ^ Default port for this daemon
263
             -> IO (Result (Socket.Family, Socket.SockAddr))
264
parseAddress opts defport = do
265
  let port = maybe defport fromIntegral $ optPort opts
266
  def_family <- Ssconf.getPrimaryIPFamily Nothing
267
  case optBindAddress opts of
268
    Nothing -> return (def_family >>= defaultBindAddr port)
269
    Just saddr -> catch (resolveAddr port saddr)
270
                  (annotateIOError $ "Invalid address " ++ saddr)
271

    
272
-- | Run an I/O action as a daemon.
273
--
274
-- WARNING: this only works in single-threaded mode (either using the
275
-- single-threaded runtime, or using the multi-threaded one but with
276
-- only one OS thread, i.e. -N1).
277
--
278
-- FIXME: this doesn't support error reporting and the prepfn
279
-- functionality.
280
daemonize :: FilePath -> IO () -> IO ()
281
daemonize logfile action = do
282
  -- first fork
283
  _ <- forkProcess $ do
284
    -- in the child
285
    setupDaemonEnv "/" (unionFileModes groupModes otherModes)
286
    setupDaemonFDs $ Just logfile
287
    _ <- installHandler lostConnection (Catch (handleSigHup logfile)) Nothing
288
    _ <- forkProcess action
289
    exitImmediately ExitSuccess
290
  exitImmediately ExitSuccess
291

    
292
-- | Generic daemon startup.
293
genericMain :: GanetiDaemon -> [OptType] -> (DaemonOptions -> IO ()) -> IO ()
294
genericMain daemon options main = do
295
  let progname = daemonName daemon
296
  (opts, args) <- parseArgs progname options
297

    
298
  exitUnless (null args) "This program doesn't take any arguments"
299

    
300
  unless (optNoUserChecks opts) $ do
301
    runtimeEnts <- getEnts
302
    ents <- exitIfBad "Can't find required user/groups" runtimeEnts
303
    verifyDaemonUser daemon ents
304

    
305
  syslog <- case optSyslogUsage opts of
306
              Nothing -> exitIfBad "Invalid cluster syslog setting" $
307
                         syslogUsageFromRaw C.syslogUsage
308
              Just v -> return v
309
  let processFn = if optDaemonize opts
310
                    then daemonize (daemonLogFile daemon)
311
                    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
  let logfile = if optDaemonize opts
320
                  then Nothing
321
                  else Just $ daemonLogFile daemon
322
  setupLogging logfile (daemonName daemon) (optDebug opts) True False syslog
323
  pid_fd <- writePidFile (daemonPidFile daemon)
324
  _ <- exitIfBad "Cannot write PID file; already locked? Error" pid_fd
325
  logNotice "starting"
326
  main