Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Daemon.hs @ 670e954a

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