Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Daemon.hs @ 13d26b66

History | View | Annotate | Download (15.8 kB)

1 6ec7a50e Iustin Pop
{-| Implementation of the generic daemon functionality.
2 6ec7a50e Iustin Pop
3 6ec7a50e Iustin Pop
-}
4 6ec7a50e Iustin Pop
5 6ec7a50e Iustin Pop
{-
6 6ec7a50e Iustin Pop
7 6ec7a50e Iustin Pop
Copyright (C) 2011, 2012 Google Inc.
8 6ec7a50e Iustin Pop
9 6ec7a50e Iustin Pop
This program is free software; you can redistribute it and/or modify
10 6ec7a50e Iustin Pop
it under the terms of the GNU General Public License as published by
11 6ec7a50e Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 6ec7a50e Iustin Pop
(at your option) any later version.
13 6ec7a50e Iustin Pop
14 6ec7a50e Iustin Pop
This program is distributed in the hope that it will be useful, but
15 6ec7a50e Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 6ec7a50e Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 6ec7a50e Iustin Pop
General Public License for more details.
18 6ec7a50e Iustin Pop
19 6ec7a50e Iustin Pop
You should have received a copy of the GNU General Public License
20 6ec7a50e Iustin Pop
along with this program; if not, write to the Free Software
21 6ec7a50e Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 6ec7a50e Iustin Pop
02110-1301, USA.
23 6ec7a50e Iustin Pop
24 6ec7a50e Iustin Pop
-}
25 6ec7a50e Iustin Pop
26 6ec7a50e Iustin Pop
module Ganeti.Daemon
27 6ec7a50e Iustin Pop
  ( DaemonOptions(..)
28 6ec7a50e Iustin Pop
  , OptType
29 2ac2e420 Iustin Pop
  , CheckFn
30 2ac2e420 Iustin Pop
  , PrepFn
31 2ac2e420 Iustin Pop
  , MainFn
32 6ec7a50e Iustin Pop
  , defaultOptions
33 6ec7a50e Iustin Pop
  , oShowHelp
34 6ec7a50e Iustin Pop
  , oShowVer
35 6ec7a50e Iustin Pop
  , oNoDaemonize
36 6ec7a50e Iustin Pop
  , oNoUserChecks
37 6ec7a50e Iustin Pop
  , oDebug
38 6ec7a50e Iustin Pop
  , oPort
39 152e05e1 Iustin Pop
  , oBindAddress
40 b714ff89 Iustin Pop
  , oSyslogUsage
41 6ec7a50e Iustin Pop
  , parseArgs
42 152e05e1 Iustin Pop
  , parseAddress
43 0d0ac025 Iustin Pop
  , cleanupSocket
44 e14b84e9 Iustin Pop
  , describeError
45 6ec7a50e Iustin Pop
  , genericMain
46 6ec7a50e Iustin Pop
  ) where
47 6ec7a50e Iustin Pop
48 80adbbe1 Michele Tartara
import Control.Concurrent
49 79ac58fa Iustin Pop
import Control.Exception
50 6ec7a50e Iustin Pop
import Control.Monad
51 ecff332f Thomas Thrainer
import Data.Maybe (fromMaybe, listToMaybe)
52 3062d395 Santi Raffa
import Text.Printf
53 6ec7a50e Iustin Pop
import Data.Word
54 0c28bee1 Iustin Pop
import GHC.IO.Handle (hDuplicateTo)
55 670e954a Thomas Thrainer
import Network.BSD (getHostName)
56 152e05e1 Iustin Pop
import qualified Network.Socket as Socket
57 6ec7a50e Iustin Pop
import System.Console.GetOpt
58 80adbbe1 Michele Tartara
import System.Directory
59 6ec7a50e Iustin Pop
import System.Exit
60 6ec7a50e Iustin Pop
import System.Environment
61 6ec7a50e Iustin Pop
import System.IO
62 e14b84e9 Iustin Pop
import System.IO.Error (isDoesNotExistError, modifyIOError, annotateIOError)
63 6ec7a50e Iustin Pop
import System.Posix.Directory
64 6ec7a50e Iustin Pop
import System.Posix.Files
65 6ec7a50e Iustin Pop
import System.Posix.IO
66 6ec7a50e Iustin Pop
import System.Posix.Process
67 6ec7a50e Iustin Pop
import System.Posix.Types
68 36691f08 Iustin Pop
import System.Posix.Signals
69 6ec7a50e Iustin Pop
70 51000365 Iustin Pop
import Ganeti.Common as Common
71 6ec7a50e Iustin Pop
import Ganeti.Logging
72 6ec7a50e Iustin Pop
import Ganeti.Runtime
73 6ec7a50e Iustin Pop
import Ganeti.BasicTypes
74 26d62e4c Iustin Pop
import Ganeti.Utils
75 6ec7a50e Iustin Pop
import qualified Ganeti.Constants as C
76 152e05e1 Iustin Pop
import qualified Ganeti.Ssconf as Ssconf
77 6ec7a50e Iustin Pop
78 0c28bee1 Iustin Pop
-- * Constants
79 0c28bee1 Iustin Pop
80 0c28bee1 Iustin Pop
-- | \/dev\/null path.
81 0c28bee1 Iustin Pop
devNull :: FilePath
82 0c28bee1 Iustin Pop
devNull = "/dev/null"
83 0c28bee1 Iustin Pop
84 b9097468 Iustin Pop
-- | Error message prefix, used in two separate paths (when forking
85 b9097468 Iustin Pop
-- and when not).
86 b9097468 Iustin Pop
daemonStartupErr :: String -> String
87 b9097468 Iustin Pop
daemonStartupErr = ("Error when starting the daemon process: " ++)
88 b9097468 Iustin Pop
89 6ec7a50e Iustin Pop
-- * Data types
90 6ec7a50e Iustin Pop
91 6ec7a50e Iustin Pop
-- | Command line options structure.
92 6ec7a50e Iustin Pop
data DaemonOptions = DaemonOptions
93 6ec7a50e Iustin Pop
  { optShowHelp     :: Bool           -- ^ Just show the help
94 6ec7a50e Iustin Pop
  , optShowVer      :: Bool           -- ^ Just show the program version
95 097ad7ee Iustin Pop
  , optShowComp     :: Bool           -- ^ Just show the completion info
96 6ec7a50e Iustin Pop
  , optDaemonize    :: Bool           -- ^ Whether to daemonize or not
97 6ec7a50e Iustin Pop
  , optPort         :: Maybe Word16   -- ^ Override for the network port
98 6ec7a50e Iustin Pop
  , optDebug        :: Bool           -- ^ Enable debug messages
99 6ec7a50e Iustin Pop
  , optNoUserChecks :: Bool           -- ^ Ignore user checks
100 152e05e1 Iustin Pop
  , optBindAddress  :: Maybe String   -- ^ Override for the bind address
101 b714ff89 Iustin Pop
  , optSyslogUsage  :: Maybe SyslogUsage -- ^ Override for Syslog usage
102 6ec7a50e Iustin Pop
  }
103 6ec7a50e Iustin Pop
104 6ec7a50e Iustin Pop
-- | Default values for the command line options.
105 6ec7a50e Iustin Pop
defaultOptions :: DaemonOptions
106 6ec7a50e Iustin Pop
defaultOptions  = DaemonOptions
107 6ec7a50e Iustin Pop
  { optShowHelp     = False
108 6ec7a50e Iustin Pop
  , optShowVer      = False
109 097ad7ee Iustin Pop
  , optShowComp     = False
110 6ec7a50e Iustin Pop
  , optDaemonize    = True
111 6ec7a50e Iustin Pop
  , optPort         = Nothing
112 6ec7a50e Iustin Pop
  , optDebug        = False
113 6ec7a50e Iustin Pop
  , optNoUserChecks = False
114 152e05e1 Iustin Pop
  , optBindAddress  = Nothing
115 b714ff89 Iustin Pop
  , optSyslogUsage  = Nothing
116 6ec7a50e Iustin Pop
  }
117 6ec7a50e Iustin Pop
118 51000365 Iustin Pop
instance StandardOptions DaemonOptions where
119 51000365 Iustin Pop
  helpRequested = optShowHelp
120 51000365 Iustin Pop
  verRequested  = optShowVer
121 097ad7ee Iustin Pop
  compRequested = optShowComp
122 5b11f8db Iustin Pop
  requestHelp o = o { optShowHelp = True }
123 5b11f8db Iustin Pop
  requestVer  o = o { optShowVer  = True }
124 097ad7ee Iustin Pop
  requestComp o = o { optShowComp = True }
125 51000365 Iustin Pop
126 6ec7a50e Iustin Pop
-- | Abrreviation for the option type.
127 51000365 Iustin Pop
type OptType = GenericOptType DaemonOptions
128 6ec7a50e Iustin Pop
129 2ac2e420 Iustin Pop
-- | Check function type.
130 2ac2e420 Iustin Pop
type CheckFn a = DaemonOptions -> IO (Either ExitCode a)
131 2ac2e420 Iustin Pop
132 2ac2e420 Iustin Pop
-- | Prepare function type.
133 2ac2e420 Iustin Pop
type PrepFn a b = DaemonOptions -> a -> IO b
134 2ac2e420 Iustin Pop
135 2ac2e420 Iustin Pop
-- | Main execution function type.
136 2ac2e420 Iustin Pop
type MainFn a b = DaemonOptions -> a -> b -> IO ()
137 2ac2e420 Iustin Pop
138 6ec7a50e Iustin Pop
-- * Command line options
139 6ec7a50e Iustin Pop
140 6ec7a50e Iustin Pop
oNoDaemonize :: OptType
141 ce207617 Iustin Pop
oNoDaemonize =
142 ce207617 Iustin Pop
  (Option "f" ["foreground"]
143 91ef0821 Jose A. Lopes
   (NoArg (\ opts -> Ok opts { optDaemonize = False }))
144 ce207617 Iustin Pop
   "Don't detach from the current terminal",
145 ce207617 Iustin Pop
   OptComplNone)
146 6ec7a50e Iustin Pop
147 6ec7a50e Iustin Pop
oDebug :: OptType
148 ce207617 Iustin Pop
oDebug =
149 ce207617 Iustin Pop
  (Option "d" ["debug"]
150 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optDebug = True }))
151 ce207617 Iustin Pop
   "Enable debug messages",
152 ce207617 Iustin Pop
   OptComplNone)
153 6ec7a50e Iustin Pop
154 6ec7a50e Iustin Pop
oNoUserChecks :: OptType
155 ce207617 Iustin Pop
oNoUserChecks =
156 ce207617 Iustin Pop
  (Option "" ["no-user-checks"]
157 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optNoUserChecks = True }))
158 ce207617 Iustin Pop
   "Ignore user checks",
159 ce207617 Iustin Pop
   OptComplNone)
160 6ec7a50e Iustin Pop
161 6ec7a50e Iustin Pop
oPort :: Int -> OptType
162 ce207617 Iustin Pop
oPort def =
163 ce207617 Iustin Pop
  (Option "p" ["port"]
164 ce207617 Iustin Pop
   (reqWithConversion (tryRead "reading port")
165 ce207617 Iustin Pop
    (\port opts -> Ok opts { optPort = Just port }) "PORT")
166 ce207617 Iustin Pop
   ("Network port (default: " ++ show def ++ ")"),
167 ecebe9f6 Iustin Pop
   OptComplInteger)
168 6ec7a50e Iustin Pop
169 152e05e1 Iustin Pop
oBindAddress :: OptType
170 ce207617 Iustin Pop
oBindAddress =
171 ce207617 Iustin Pop
  (Option "b" ["bind"]
172 ce207617 Iustin Pop
   (ReqArg (\addr opts -> Ok opts { optBindAddress = Just addr })
173 ce207617 Iustin Pop
    "ADDR")
174 ce207617 Iustin Pop
   "Bind address (default depends on cluster configuration)",
175 ce207617 Iustin Pop
   OptComplInetAddr)
176 152e05e1 Iustin Pop
177 b714ff89 Iustin Pop
oSyslogUsage :: OptType
178 ce207617 Iustin Pop
oSyslogUsage =
179 ce207617 Iustin Pop
  (Option "" ["syslog"]
180 ce207617 Iustin Pop
   (reqWithConversion syslogUsageFromRaw
181 ce207617 Iustin Pop
    (\su opts -> Ok opts { optSyslogUsage = Just su })
182 ce207617 Iustin Pop
    "SYSLOG")
183 ce207617 Iustin Pop
   ("Enable logging to syslog (except debug \
184 ce207617 Iustin Pop
    \messages); one of 'no', 'yes' or 'only' [" ++ C.syslogUsage ++
185 ce207617 Iustin Pop
    "]"),
186 ce207617 Iustin Pop
   OptComplChoices ["yes", "no", "only"])
187 b714ff89 Iustin Pop
188 42834645 Iustin Pop
-- | Generic options.
189 42834645 Iustin Pop
genericOpts :: [OptType]
190 42834645 Iustin Pop
genericOpts = [ oShowHelp
191 42834645 Iustin Pop
              , oShowVer
192 097ad7ee Iustin Pop
              , oShowComp
193 42834645 Iustin Pop
              ]
194 42834645 Iustin Pop
195 7413b229 Iustin Pop
-- | Annotates and transforms IOErrors into a Result type. This can be
196 7413b229 Iustin Pop
-- used in the error handler argument to 'catch', for example.
197 7413b229 Iustin Pop
ioErrorToResult :: String -> IOError -> IO (Result a)
198 7413b229 Iustin Pop
ioErrorToResult description exc =
199 7413b229 Iustin Pop
  return . Bad $ description ++ ": " ++ show exc
200 7413b229 Iustin Pop
201 6ec7a50e Iustin Pop
-- | Small wrapper over getArgs and 'parseOpts'.
202 6ec7a50e Iustin Pop
parseArgs :: String -> [OptType] -> IO (DaemonOptions, [String])
203 6ec7a50e Iustin Pop
parseArgs cmd options = do
204 6ec7a50e Iustin Pop
  cmd_args <- getArgs
205 22278fa7 Iustin Pop
  parseOpts defaultOptions cmd_args cmd (options ++ genericOpts) []
206 6ec7a50e Iustin Pop
207 6ec7a50e Iustin Pop
-- * Daemon-related functions
208 a4c0fe1e Iustin Pop
209 6ec7a50e Iustin Pop
-- | PID file mode.
210 6ec7a50e Iustin Pop
pidFileMode :: FileMode
211 6ec7a50e Iustin Pop
pidFileMode = unionFileModes ownerReadMode ownerWriteMode
212 6ec7a50e Iustin Pop
213 a4c0fe1e Iustin Pop
-- | PID file open flags.
214 a4c0fe1e Iustin Pop
pidFileFlags :: OpenFileFlags
215 a4c0fe1e Iustin Pop
pidFileFlags = defaultFileFlags { noctty = True, trunc = False }
216 a4c0fe1e Iustin Pop
217 6ec7a50e Iustin Pop
-- | Writes a PID file and locks it.
218 e14b84e9 Iustin Pop
writePidFile :: FilePath -> IO Fd
219 e14b84e9 Iustin Pop
writePidFile path = do
220 a4c0fe1e Iustin Pop
  fd <- openFd path ReadWrite (Just pidFileMode) pidFileFlags
221 6ec7a50e Iustin Pop
  setLock fd (WriteLock, AbsoluteSeek, 0, 0)
222 6ec7a50e Iustin Pop
  my_pid <- getProcessID
223 6ec7a50e Iustin Pop
  _ <- fdWrite fd (show my_pid ++ "\n")
224 6ec7a50e Iustin Pop
  return fd
225 6ec7a50e Iustin Pop
226 0d0ac025 Iustin Pop
-- | Helper function to ensure a socket doesn't exist. Should only be
227 0d0ac025 Iustin Pop
-- called once we have locked the pid file successfully.
228 0d0ac025 Iustin Pop
cleanupSocket :: FilePath -> IO ()
229 5b11f8db Iustin Pop
cleanupSocket socketPath =
230 0d0ac025 Iustin Pop
  catchJust (guard . isDoesNotExistError) (removeLink socketPath)
231 0d0ac025 Iustin Pop
            (const $ return ())
232 0d0ac025 Iustin Pop
233 6ec7a50e Iustin Pop
-- | Sets up a daemon's environment.
234 6ec7a50e Iustin Pop
setupDaemonEnv :: FilePath -> FileMode -> IO ()
235 6ec7a50e Iustin Pop
setupDaemonEnv cwd umask = do
236 6ec7a50e Iustin Pop
  changeWorkingDirectory cwd
237 6ec7a50e Iustin Pop
  _ <- setFileCreationMask umask
238 6ec7a50e Iustin Pop
  _ <- createSession
239 6ec7a50e Iustin Pop
  return ()
240 6ec7a50e Iustin Pop
241 80adbbe1 Michele Tartara
-- | Cleanup function, performing all the operations that need to be done prior
242 80adbbe1 Michele Tartara
-- to shutting down a daemon.
243 80adbbe1 Michele Tartara
finalCleanup :: FilePath -> IO ()
244 80adbbe1 Michele Tartara
finalCleanup = removeFile
245 80adbbe1 Michele Tartara
246 80adbbe1 Michele Tartara
-- | Signal handler for the termination signal.
247 80adbbe1 Michele Tartara
handleSigTerm :: ThreadId -> IO ()
248 80adbbe1 Michele Tartara
handleSigTerm mainTID =
249 80adbbe1 Michele Tartara
  -- Throw termination exception to the main thread, so that the daemon is
250 80adbbe1 Michele Tartara
  -- actually stopped in the proper way, executing all the functions waiting on
251 80adbbe1 Michele Tartara
  -- "finally" statement.
252 80adbbe1 Michele Tartara
  Control.Exception.throwTo mainTID ExitSuccess
253 80adbbe1 Michele Tartara
254 36691f08 Iustin Pop
-- | Signal handler for reopening log files.
255 36691f08 Iustin Pop
handleSigHup :: FilePath -> IO ()
256 36691f08 Iustin Pop
handleSigHup path = do
257 36691f08 Iustin Pop
  setupDaemonFDs (Just path)
258 36691f08 Iustin Pop
  logInfo "Reopening log files after receiving SIGHUP"
259 36691f08 Iustin Pop
260 0c28bee1 Iustin Pop
-- | Sets up a daemon's standard file descriptors.
261 0c28bee1 Iustin Pop
setupDaemonFDs :: Maybe FilePath -> IO ()
262 0c28bee1 Iustin Pop
setupDaemonFDs logfile = do
263 0c28bee1 Iustin Pop
  null_in_handle <- openFile devNull ReadMode
264 0c28bee1 Iustin Pop
  null_out_handle <- openFile (fromMaybe devNull logfile) AppendMode
265 0c28bee1 Iustin Pop
  hDuplicateTo null_in_handle stdin
266 0c28bee1 Iustin Pop
  hDuplicateTo null_out_handle stdout
267 0c28bee1 Iustin Pop
  hDuplicateTo null_out_handle stderr
268 0c28bee1 Iustin Pop
  hClose null_in_handle
269 0c28bee1 Iustin Pop
  hClose null_out_handle
270 0c28bee1 Iustin Pop
271 152e05e1 Iustin Pop
-- | Computes the default bind address for a given family.
272 152e05e1 Iustin Pop
defaultBindAddr :: Int                  -- ^ The port we want
273 152e05e1 Iustin Pop
                -> Socket.Family        -- ^ The cluster IP family
274 152e05e1 Iustin Pop
                -> Result (Socket.Family, Socket.SockAddr)
275 152e05e1 Iustin Pop
defaultBindAddr port Socket.AF_INET =
276 5b11f8db Iustin Pop
  Ok (Socket.AF_INET,
277 5b11f8db Iustin Pop
      Socket.SockAddrInet (fromIntegral port) Socket.iNADDR_ANY)
278 152e05e1 Iustin Pop
defaultBindAddr port Socket.AF_INET6 =
279 5b11f8db Iustin Pop
  Ok (Socket.AF_INET6,
280 5b11f8db Iustin Pop
      Socket.SockAddrInet6 (fromIntegral port) 0 Socket.iN6ADDR_ANY 0)
281 152e05e1 Iustin Pop
defaultBindAddr _ fam = Bad $ "Unsupported address family: " ++ show fam
282 152e05e1 Iustin Pop
283 152e05e1 Iustin Pop
-- | Based on the options, compute the socket address to use for the
284 152e05e1 Iustin Pop
-- daemon.
285 152e05e1 Iustin Pop
parseAddress :: DaemonOptions      -- ^ Command line options
286 152e05e1 Iustin Pop
             -> Int                -- ^ Default port for this daemon
287 152e05e1 Iustin Pop
             -> IO (Result (Socket.Family, Socket.SockAddr))
288 152e05e1 Iustin Pop
parseAddress opts defport = do
289 152e05e1 Iustin Pop
  let port = maybe defport fromIntegral $ optPort opts
290 152e05e1 Iustin Pop
  def_family <- Ssconf.getPrimaryIPFamily Nothing
291 5b11f8db Iustin Pop
  case optBindAddress opts of
292 5b11f8db Iustin Pop
    Nothing -> return (def_family >>= defaultBindAddr port)
293 b9612abb Iustin Pop
    Just saddr -> Control.Exception.catch
294 b9612abb Iustin Pop
                    (resolveAddr port saddr)
295 7413b229 Iustin Pop
                    (ioErrorToResult $ "Invalid address " ++ saddr)
296 152e05e1 Iustin Pop
297 670e954a Thomas Thrainer
-- | Environment variable to override the assumed host name of the
298 670e954a Thomas Thrainer
-- current node.
299 670e954a Thomas Thrainer
vClusterHostNameEnvVar :: String
300 670e954a Thomas Thrainer
vClusterHostNameEnvVar = "GANETI_HOSTNAME"
301 670e954a Thomas Thrainer
302 ecff332f Thomas Thrainer
getFQDN :: IO String
303 ecff332f Thomas Thrainer
getFQDN = do
304 ecff332f Thomas Thrainer
  hostname <- getHostName
305 ecff332f Thomas Thrainer
  addrInfos <- Socket.getAddrInfo Nothing (Just hostname) Nothing
306 ecff332f Thomas Thrainer
  let address = listToMaybe addrInfos >>= (Just . Socket.addrAddress)
307 ecff332f Thomas Thrainer
  case address of
308 ecff332f Thomas Thrainer
    Just a -> do
309 ecff332f Thomas Thrainer
      fqdn <- liftM fst $ Socket.getNameInfo [] True False a
310 ecff332f Thomas Thrainer
      return (fromMaybe hostname fqdn)
311 ecff332f Thomas Thrainer
    Nothing -> return hostname
312 ecff332f Thomas Thrainer
313 670e954a Thomas Thrainer
-- | Returns if the current node is the master node.
314 670e954a Thomas Thrainer
isMaster :: IO Bool
315 670e954a Thomas Thrainer
isMaster = do
316 670e954a Thomas Thrainer
  let ioErrorToNothing :: IOError -> IO (Maybe String)
317 670e954a Thomas Thrainer
      ioErrorToNothing _ = return Nothing
318 670e954a Thomas Thrainer
  vcluster_node <- Control.Exception.catch
319 670e954a Thomas Thrainer
                     (liftM Just (getEnv vClusterHostNameEnvVar))
320 670e954a Thomas Thrainer
                     ioErrorToNothing
321 670e954a Thomas Thrainer
  curNode <- case vcluster_node of
322 670e954a Thomas Thrainer
    Just node_name -> return node_name
323 ecff332f Thomas Thrainer
    Nothing -> getFQDN
324 670e954a Thomas Thrainer
  masterNode <- Ssconf.getMasterNode Nothing
325 670e954a Thomas Thrainer
  case masterNode of
326 670e954a Thomas Thrainer
    Ok n -> return (curNode == n)
327 670e954a Thomas Thrainer
    Bad _ -> return False
328 670e954a Thomas Thrainer
329 670e954a Thomas Thrainer
-- | Ensures that the daemon runs on the right node (and exits
330 670e954a Thomas Thrainer
-- gracefully if it doesnt)
331 670e954a Thomas Thrainer
ensureNode :: GanetiDaemon -> IO ()
332 670e954a Thomas Thrainer
ensureNode daemon = do
333 670e954a Thomas Thrainer
  is_master <- isMaster
334 670e954a Thomas Thrainer
  when (daemonOnlyOnMaster daemon && not is_master) $ do
335 670e954a Thomas Thrainer
    putStrLn "Not master, exiting."
336 670e954a Thomas Thrainer
    exitWith (ExitFailure C.exitNotmaster)
337 670e954a Thomas Thrainer
338 e14b84e9 Iustin Pop
-- | Run an I\/O action that might throw an I\/O error, under a
339 e14b84e9 Iustin Pop
-- handler that will simply annotate and re-throw the exception.
340 e14b84e9 Iustin Pop
describeError :: String -> Maybe Handle -> Maybe FilePath -> IO a -> IO a
341 e14b84e9 Iustin Pop
describeError descr hndl fpath =
342 e14b84e9 Iustin Pop
  modifyIOError (\e -> annotateIOError e descr hndl fpath)
343 e14b84e9 Iustin Pop
344 e14b84e9 Iustin Pop
-- | Run an I\/O action as a daemon.
345 6ec7a50e Iustin Pop
--
346 6ec7a50e Iustin Pop
-- WARNING: this only works in single-threaded mode (either using the
347 6ec7a50e Iustin Pop
-- single-threaded runtime, or using the multi-threaded one but with
348 6ec7a50e Iustin Pop
-- only one OS thread, i.e. -N1).
349 b9097468 Iustin Pop
daemonize :: FilePath -> (Maybe Fd -> IO ()) -> IO ()
350 0c28bee1 Iustin Pop
daemonize logfile action = do
351 b9097468 Iustin Pop
  (rpipe, wpipe) <- createPipe
352 6ec7a50e Iustin Pop
  -- first fork
353 6ec7a50e Iustin Pop
  _ <- forkProcess $ do
354 6ec7a50e Iustin Pop
    -- in the child
355 b9097468 Iustin Pop
    closeFd rpipe
356 1a865afe Iustin Pop
    let wpipe' = Just wpipe
357 6ec7a50e Iustin Pop
    setupDaemonEnv "/" (unionFileModes groupModes otherModes)
358 1a865afe Iustin Pop
    setupDaemonFDs (Just logfile) `Control.Exception.catch`
359 1a865afe Iustin Pop
      handlePrepErr False wpipe'
360 36691f08 Iustin Pop
    _ <- installHandler lostConnection (Catch (handleSigHup logfile)) Nothing
361 b9097468 Iustin Pop
    -- second fork, launches the actual child code; standard
362 b9097468 Iustin Pop
    -- double-fork technique
363 1a865afe Iustin Pop
    _ <- forkProcess (action wpipe')
364 6ec7a50e Iustin Pop
    exitImmediately ExitSuccess
365 b9097468 Iustin Pop
  closeFd wpipe
366 b9097468 Iustin Pop
  hndl <- fdToHandle rpipe
367 b9097468 Iustin Pop
  errors <- hGetContents hndl
368 b9097468 Iustin Pop
  ecode <- if null errors
369 b9097468 Iustin Pop
             then return ExitSuccess
370 b9097468 Iustin Pop
             else do
371 b9097468 Iustin Pop
               hPutStrLn stderr $ daemonStartupErr errors
372 b9097468 Iustin Pop
               return $ ExitFailure C.exitFailure
373 b9097468 Iustin Pop
  exitImmediately ecode
374 6ec7a50e Iustin Pop
375 6ec7a50e Iustin Pop
-- | Generic daemon startup.
376 2ac2e420 Iustin Pop
genericMain :: GanetiDaemon -- ^ The daemon we're running
377 2ac2e420 Iustin Pop
            -> [OptType]    -- ^ The available options
378 2ac2e420 Iustin Pop
            -> CheckFn a    -- ^ Check function
379 2ac2e420 Iustin Pop
            -> PrepFn  a b  -- ^ Prepare function
380 2ac2e420 Iustin Pop
            -> MainFn  a b  -- ^ Execution function
381 2ac2e420 Iustin Pop
            -> IO ()
382 2ac2e420 Iustin Pop
genericMain daemon options check_fn prep_fn exec_fn = do
383 6ec7a50e Iustin Pop
  let progname = daemonName daemon
384 670e954a Thomas Thrainer
385 6ec7a50e Iustin Pop
  (opts, args) <- parseArgs progname options
386 6ec7a50e Iustin Pop
387 3062d395 Santi Raffa
  -- Modify handleClient in Ganeti.UDSServer to remove this logging from luxid.
388 3062d395 Santi Raffa
  when (optDebug opts && daemon == GanetiLuxid) .
389 3062d395 Santi Raffa
    hPutStrLn stderr $
390 3062d395 Santi Raffa
      printf C.debugModeConfidentialityWarning (daemonName daemon)
391 3062d395 Santi Raffa
392 670e954a Thomas Thrainer
  ensureNode daemon
393 670e954a Thomas Thrainer
394 88a10df5 Iustin Pop
  exitUnless (null args) "This program doesn't take any arguments"
395 6ec7a50e Iustin Pop
396 6ec7a50e Iustin Pop
  unless (optNoUserChecks opts) $ do
397 6ec7a50e Iustin Pop
    runtimeEnts <- getEnts
398 88a10df5 Iustin Pop
    ents <- exitIfBad "Can't find required user/groups" runtimeEnts
399 88a10df5 Iustin Pop
    verifyDaemonUser daemon ents
400 6ec7a50e Iustin Pop
401 b714ff89 Iustin Pop
  syslog <- case optSyslogUsage opts of
402 88a10df5 Iustin Pop
              Nothing -> exitIfBad "Invalid cluster syslog setting" $
403 b714ff89 Iustin Pop
                         syslogUsageFromRaw C.syslogUsage
404 b714ff89 Iustin Pop
              Just v -> return v
405 2ac2e420 Iustin Pop
406 29a30533 Iustin Pop
  log_file <- daemonLogFile daemon
407 2ac2e420 Iustin Pop
  -- run the check function and optionally exit if it returns an exit code
408 2ac2e420 Iustin Pop
  check_result <- check_fn opts
409 2ac2e420 Iustin Pop
  check_result' <- case check_result of
410 2ac2e420 Iustin Pop
                     Left code -> exitWith code
411 2ac2e420 Iustin Pop
                     Right v -> return v
412 2ac2e420 Iustin Pop
413 0c28bee1 Iustin Pop
  let processFn = if optDaemonize opts
414 29a30533 Iustin Pop
                    then daemonize log_file
415 b9097468 Iustin Pop
                    else \action -> action Nothing
416 2ac2e420 Iustin Pop
  processFn $ innerMain daemon opts syslog check_result' prep_fn exec_fn
417 6ec7a50e Iustin Pop
418 b9097468 Iustin Pop
-- | Full prepare function.
419 b9097468 Iustin Pop
--
420 b9097468 Iustin Pop
-- This is executed after daemonization, and sets up both the log
421 b9097468 Iustin Pop
-- files (a generic functionality) and the custom prepare function of
422 b9097468 Iustin Pop
-- the daemon.
423 b9097468 Iustin Pop
fullPrep :: GanetiDaemon  -- ^ The daemon we're running
424 b9097468 Iustin Pop
         -> DaemonOptions -- ^ The options structure, filled from the cmdline
425 b9097468 Iustin Pop
         -> SyslogUsage   -- ^ Syslog mode
426 b9097468 Iustin Pop
         -> a             -- ^ Check results
427 b9097468 Iustin Pop
         -> PrepFn a b    -- ^ Prepare function
428 80adbbe1 Michele Tartara
         -> IO (FilePath, b)
429 b9097468 Iustin Pop
fullPrep daemon opts syslog check_result prep_fn = do
430 29a30533 Iustin Pop
  logfile <- if optDaemonize opts
431 29a30533 Iustin Pop
               then return Nothing
432 29a30533 Iustin Pop
               else liftM Just $ daemonLogFile daemon
433 29a30533 Iustin Pop
  pidfile <- daemonPidFile daemon
434 29a30533 Iustin Pop
  let dname = daemonName daemon
435 48483a2e Iustin Pop
  setupLogging logfile dname (optDebug opts) True False syslog
436 e14b84e9 Iustin Pop
  _ <- describeError "writing PID file; already locked?"
437 e14b84e9 Iustin Pop
         Nothing (Just pidfile) $ writePidFile pidfile
438 48483a2e Iustin Pop
  logNotice $ dname ++ " daemon startup"
439 80adbbe1 Michele Tartara
  prep_res <- prep_fn opts check_result
440 80adbbe1 Michele Tartara
  tid <- myThreadId
441 80adbbe1 Michele Tartara
  _ <- installHandler sigTERM (Catch $ handleSigTerm tid) Nothing
442 80adbbe1 Michele Tartara
  return (pidfile, prep_res)
443 b9097468 Iustin Pop
444 6ec7a50e Iustin Pop
-- | Inner daemon function.
445 6ec7a50e Iustin Pop
--
446 6ec7a50e Iustin Pop
-- This is executed after daemonization.
447 2ac2e420 Iustin Pop
innerMain :: GanetiDaemon  -- ^ The daemon we're running
448 2ac2e420 Iustin Pop
          -> DaemonOptions -- ^ The options structure, filled from the cmdline
449 2ac2e420 Iustin Pop
          -> SyslogUsage   -- ^ Syslog mode
450 2ac2e420 Iustin Pop
          -> a             -- ^ Check results
451 2ac2e420 Iustin Pop
          -> PrepFn a b    -- ^ Prepare function
452 2ac2e420 Iustin Pop
          -> MainFn a b    -- ^ Execution function
453 b9097468 Iustin Pop
          -> Maybe Fd      -- ^ Error reporting function
454 2ac2e420 Iustin Pop
          -> IO ()
455 b9097468 Iustin Pop
innerMain daemon opts syslog check_result prep_fn exec_fn fd = do
456 80adbbe1 Michele Tartara
  (pidFile, prep_result) <- fullPrep daemon opts syslog check_result prep_fn
457 1a865afe Iustin Pop
                 `Control.Exception.catch` handlePrepErr True fd
458 b9097468 Iustin Pop
  -- no error reported, we should now close the fd
459 b9097468 Iustin Pop
  maybeCloseFd fd
460 80adbbe1 Michele Tartara
  finally (exec_fn opts check_result prep_result) (finalCleanup pidFile)
461 b9097468 Iustin Pop
462 b9097468 Iustin Pop
-- | Daemon prepare error handling function.
463 1a865afe Iustin Pop
handlePrepErr :: Bool -> Maybe Fd -> IOError -> IO a
464 1a865afe Iustin Pop
handlePrepErr logging_setup fd err = do
465 b9097468 Iustin Pop
  let msg = show err
466 b9097468 Iustin Pop
  case fd of
467 b9097468 Iustin Pop
    -- explicitly writing to the fd directly, since when forking it's
468 b9097468 Iustin Pop
    -- better (safer) than trying to convert this into a full handle
469 b9097468 Iustin Pop
    Just fd' -> fdWrite fd' msg >> return ()
470 b9097468 Iustin Pop
    Nothing  -> hPutStrLn stderr (daemonStartupErr msg)
471 1a865afe Iustin Pop
  when logging_setup $ logError msg
472 b9097468 Iustin Pop
  exitWith $ ExitFailure 1
473 b9097468 Iustin Pop
474 b9097468 Iustin Pop
-- | Close a file descriptor.
475 b9097468 Iustin Pop
maybeCloseFd :: Maybe Fd -> IO ()
476 b9097468 Iustin Pop
maybeCloseFd Nothing   = return ()
477 b9097468 Iustin Pop
maybeCloseFd (Just fd) = closeFd fd