Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Daemon.hs @ a4c0fe1e

History | View | Annotate | Download (12.2 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 6ec7a50e Iustin Pop
  , defaultOptions
30 6ec7a50e Iustin Pop
  , oShowHelp
31 6ec7a50e Iustin Pop
  , oShowVer
32 6ec7a50e Iustin Pop
  , oNoDaemonize
33 6ec7a50e Iustin Pop
  , oNoUserChecks
34 6ec7a50e Iustin Pop
  , oDebug
35 6ec7a50e Iustin Pop
  , oPort
36 152e05e1 Iustin Pop
  , oBindAddress
37 b714ff89 Iustin Pop
  , oSyslogUsage
38 6ec7a50e Iustin Pop
  , parseArgs
39 152e05e1 Iustin Pop
  , parseAddress
40 6ec7a50e Iustin Pop
  , writePidFile
41 6ec7a50e Iustin Pop
  , genericMain
42 6ec7a50e Iustin Pop
  ) where
43 6ec7a50e Iustin Pop
44 79ac58fa Iustin Pop
import Control.Exception
45 6ec7a50e Iustin Pop
import Control.Monad
46 0c28bee1 Iustin Pop
import Data.Maybe (fromMaybe)
47 6ec7a50e Iustin Pop
import qualified Data.Version
48 6ec7a50e Iustin Pop
import Data.Word
49 0c28bee1 Iustin Pop
import GHC.IO.Handle (hDuplicateTo)
50 152e05e1 Iustin Pop
import qualified Network.Socket as Socket
51 6ec7a50e Iustin Pop
import System.Console.GetOpt
52 6ec7a50e Iustin Pop
import System.Exit
53 6ec7a50e Iustin Pop
import System.Environment
54 6ec7a50e Iustin Pop
import System.Info
55 6ec7a50e Iustin Pop
import System.IO
56 6ec7a50e Iustin Pop
import System.Posix.Directory
57 6ec7a50e Iustin Pop
import System.Posix.Files
58 6ec7a50e Iustin Pop
import System.Posix.IO
59 6ec7a50e Iustin Pop
import System.Posix.Process
60 6ec7a50e Iustin Pop
import System.Posix.Types
61 36691f08 Iustin Pop
import System.Posix.Signals
62 6ec7a50e Iustin Pop
import Text.Printf
63 6ec7a50e Iustin Pop
64 6ec7a50e Iustin Pop
import Ganeti.Logging
65 6ec7a50e Iustin Pop
import Ganeti.Runtime
66 6ec7a50e Iustin Pop
import Ganeti.BasicTypes
67 6ec7a50e Iustin Pop
import Ganeti.HTools.Utils
68 6ec7a50e Iustin Pop
import qualified Ganeti.HTools.Version as Version(version)
69 6ec7a50e Iustin Pop
import qualified Ganeti.Constants as C
70 152e05e1 Iustin Pop
import qualified Ganeti.Ssconf as Ssconf
71 6ec7a50e Iustin Pop
72 0c28bee1 Iustin Pop
-- * Constants
73 0c28bee1 Iustin Pop
74 0c28bee1 Iustin Pop
-- | \/dev\/null path.
75 0c28bee1 Iustin Pop
devNull :: FilePath
76 0c28bee1 Iustin Pop
devNull = "/dev/null"
77 0c28bee1 Iustin Pop
78 6ec7a50e Iustin Pop
-- * Data types
79 6ec7a50e Iustin Pop
80 6ec7a50e Iustin Pop
-- | Command line options structure.
81 6ec7a50e Iustin Pop
data DaemonOptions = DaemonOptions
82 6ec7a50e Iustin Pop
  { optShowHelp     :: Bool           -- ^ Just show the help
83 6ec7a50e Iustin Pop
  , optShowVer      :: Bool           -- ^ Just show the program version
84 6ec7a50e Iustin Pop
  , optDaemonize    :: Bool           -- ^ Whether to daemonize or not
85 6ec7a50e Iustin Pop
  , optPort         :: Maybe Word16   -- ^ Override for the network port
86 6ec7a50e Iustin Pop
  , optDebug        :: Bool           -- ^ Enable debug messages
87 6ec7a50e Iustin Pop
  , optNoUserChecks :: Bool           -- ^ Ignore user checks
88 152e05e1 Iustin Pop
  , optBindAddress  :: Maybe String   -- ^ Override for the bind address
89 b714ff89 Iustin Pop
  , optSyslogUsage  :: Maybe SyslogUsage -- ^ Override for Syslog usage
90 6ec7a50e Iustin Pop
  }
91 6ec7a50e Iustin Pop
92 6ec7a50e Iustin Pop
-- | Default values for the command line options.
93 6ec7a50e Iustin Pop
defaultOptions :: DaemonOptions
94 6ec7a50e Iustin Pop
defaultOptions  = DaemonOptions
95 6ec7a50e Iustin Pop
  { optShowHelp     = False
96 6ec7a50e Iustin Pop
  , optShowVer      = False
97 6ec7a50e Iustin Pop
  , optDaemonize    = True
98 6ec7a50e Iustin Pop
  , optPort         = Nothing
99 6ec7a50e Iustin Pop
  , optDebug        = False
100 6ec7a50e Iustin Pop
  , optNoUserChecks = False
101 152e05e1 Iustin Pop
  , optBindAddress  = Nothing
102 b714ff89 Iustin Pop
  , optSyslogUsage  = Nothing
103 6ec7a50e Iustin Pop
  }
104 6ec7a50e Iustin Pop
105 6ec7a50e Iustin Pop
-- | Abrreviation for the option type.
106 6ec7a50e Iustin Pop
type OptType = OptDescr (DaemonOptions -> Result DaemonOptions)
107 6ec7a50e Iustin Pop
108 6ec7a50e Iustin Pop
-- | Helper function for required arguments which need to be converted
109 6ec7a50e Iustin Pop
-- as opposed to stored just as string.
110 6ec7a50e Iustin Pop
reqWithConversion :: (String -> Result a)
111 6ec7a50e Iustin Pop
                  -> (a -> DaemonOptions -> Result DaemonOptions)
112 6ec7a50e Iustin Pop
                  -> String
113 6ec7a50e Iustin Pop
                  -> ArgDescr (DaemonOptions -> Result DaemonOptions)
114 6ec7a50e Iustin Pop
reqWithConversion conversion_fn updater_fn metavar =
115 6ec7a50e Iustin Pop
  ReqArg (\string_opt opts -> do
116 6ec7a50e Iustin Pop
            parsed_value <- conversion_fn string_opt
117 6ec7a50e Iustin Pop
            updater_fn parsed_value opts) metavar
118 6ec7a50e Iustin Pop
119 6ec7a50e Iustin Pop
-- * Command line options
120 6ec7a50e Iustin Pop
121 6ec7a50e Iustin Pop
oShowHelp :: OptType
122 6ec7a50e Iustin Pop
oShowHelp = Option "h" ["help"]
123 6ec7a50e Iustin Pop
            (NoArg (\ opts -> Ok opts { optShowHelp = True}))
124 6ec7a50e Iustin Pop
            "Show the help message and exit"
125 6ec7a50e Iustin Pop
126 6ec7a50e Iustin Pop
oShowVer :: OptType
127 6ec7a50e Iustin Pop
oShowVer = Option "V" ["version"]
128 6ec7a50e Iustin Pop
           (NoArg (\ opts -> Ok opts { optShowVer = True}))
129 6ec7a50e Iustin Pop
           "Show the version of the program and exit"
130 6ec7a50e Iustin Pop
131 6ec7a50e Iustin Pop
oNoDaemonize :: OptType
132 6ec7a50e Iustin Pop
oNoDaemonize = Option "f" ["foreground"]
133 6ec7a50e Iustin Pop
               (NoArg (\ opts -> Ok opts { optDaemonize = False}))
134 6ec7a50e Iustin Pop
               "Don't detach from the current terminal"
135 6ec7a50e Iustin Pop
136 6ec7a50e Iustin Pop
oDebug :: OptType
137 6ec7a50e Iustin Pop
oDebug = Option "d" ["debug"]
138 6ec7a50e Iustin Pop
         (NoArg (\ opts -> Ok opts { optDebug = True }))
139 6ec7a50e Iustin Pop
         "Enable debug messages"
140 6ec7a50e Iustin Pop
141 6ec7a50e Iustin Pop
oNoUserChecks :: OptType
142 6ec7a50e Iustin Pop
oNoUserChecks = Option "" ["no-user-checks"]
143 6ec7a50e Iustin Pop
         (NoArg (\ opts -> Ok opts { optNoUserChecks = True }))
144 6ec7a50e Iustin Pop
         "Ignore user checks"
145 6ec7a50e Iustin Pop
146 6ec7a50e Iustin Pop
oPort :: Int -> OptType
147 e6812a1a Iustin Pop
oPort def = Option "p" ["port"]
148 6ec7a50e Iustin Pop
            (reqWithConversion (tryRead "reading port")
149 6ec7a50e Iustin Pop
             (\port opts -> Ok opts { optPort = Just port }) "PORT")
150 6ec7a50e Iustin Pop
            ("Network port (default: " ++ show def ++ ")")
151 6ec7a50e Iustin Pop
152 152e05e1 Iustin Pop
oBindAddress :: OptType
153 152e05e1 Iustin Pop
oBindAddress = Option "b" ["bind"]
154 152e05e1 Iustin Pop
               (ReqArg (\addr opts -> Ok opts { optBindAddress = Just addr })
155 152e05e1 Iustin Pop
                "ADDR")
156 152e05e1 Iustin Pop
               "Bind address (default depends on cluster configuration)"
157 152e05e1 Iustin Pop
158 b714ff89 Iustin Pop
oSyslogUsage :: OptType
159 b714ff89 Iustin Pop
oSyslogUsage = Option "" ["syslog"]
160 b714ff89 Iustin Pop
               (reqWithConversion syslogUsageFromRaw
161 b714ff89 Iustin Pop
                (\su opts -> Ok opts { optSyslogUsage = Just su })
162 b714ff89 Iustin Pop
                "SYSLOG")
163 b714ff89 Iustin Pop
               ("Enable logging to syslog (except debug \
164 b714ff89 Iustin Pop
                \messages); one of 'no', 'yes' or 'only' [" ++ C.syslogUsage ++
165 b714ff89 Iustin Pop
                "]")
166 b714ff89 Iustin Pop
167 6ec7a50e Iustin Pop
-- | Usage info.
168 6ec7a50e Iustin Pop
usageHelp :: String -> [OptType] -> String
169 6ec7a50e Iustin Pop
usageHelp progname =
170 6ec7a50e Iustin Pop
  usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
171 6ec7a50e Iustin Pop
             progname Version.version progname)
172 6ec7a50e Iustin Pop
173 6ec7a50e Iustin Pop
-- | Command line parser, using the 'Options' structure.
174 6ec7a50e Iustin Pop
parseOpts :: [String]               -- ^ The command line arguments
175 6ec7a50e Iustin Pop
          -> String                 -- ^ The program name
176 6ec7a50e Iustin Pop
          -> [OptType]              -- ^ The supported command line options
177 6ec7a50e Iustin Pop
          -> IO (DaemonOptions, [String]) -- ^ The resulting options
178 6ec7a50e Iustin Pop
                                          -- and leftover arguments
179 6ec7a50e Iustin Pop
parseOpts argv progname options =
180 6ec7a50e Iustin Pop
  case getOpt Permute options argv of
181 6ec7a50e Iustin Pop
    (opt_list, args, []) ->
182 6ec7a50e Iustin Pop
      do
183 6ec7a50e Iustin Pop
        parsed_opts <-
184 88a10df5 Iustin Pop
          exitIfBad "Error while parsing command line arguments" $
185 88a10df5 Iustin Pop
          foldM (flip id) defaultOptions opt_list
186 6ec7a50e Iustin Pop
        return (parsed_opts, args)
187 6ec7a50e Iustin Pop
    (_, _, errs) -> do
188 6ec7a50e Iustin Pop
      hPutStrLn stderr $ "Command line error: "  ++ concat errs
189 6ec7a50e Iustin Pop
      hPutStrLn stderr $ usageHelp progname options
190 6ec7a50e Iustin Pop
      exitWith $ ExitFailure 2
191 6ec7a50e Iustin Pop
192 6ec7a50e Iustin Pop
-- | Small wrapper over getArgs and 'parseOpts'.
193 6ec7a50e Iustin Pop
parseArgs :: String -> [OptType] -> IO (DaemonOptions, [String])
194 6ec7a50e Iustin Pop
parseArgs cmd options = do
195 6ec7a50e Iustin Pop
  cmd_args <- getArgs
196 6ec7a50e Iustin Pop
  parseOpts cmd_args cmd options
197 6ec7a50e Iustin Pop
198 6ec7a50e Iustin Pop
-- * Daemon-related functions
199 a4c0fe1e Iustin Pop
200 6ec7a50e Iustin Pop
-- | PID file mode.
201 6ec7a50e Iustin Pop
pidFileMode :: FileMode
202 6ec7a50e Iustin Pop
pidFileMode = unionFileModes ownerReadMode ownerWriteMode
203 6ec7a50e Iustin Pop
204 a4c0fe1e Iustin Pop
-- | PID file open flags.
205 a4c0fe1e Iustin Pop
pidFileFlags :: OpenFileFlags
206 a4c0fe1e Iustin Pop
pidFileFlags = defaultFileFlags { noctty = True, trunc = False }
207 a4c0fe1e Iustin Pop
208 6ec7a50e Iustin Pop
-- | Writes a PID file and locks it.
209 6ec7a50e Iustin Pop
_writePidFile :: FilePath -> IO Fd
210 6ec7a50e Iustin Pop
_writePidFile path = do
211 a4c0fe1e Iustin Pop
  fd <- openFd path ReadWrite (Just pidFileMode) pidFileFlags
212 6ec7a50e Iustin Pop
  setLock fd (WriteLock, AbsoluteSeek, 0, 0)
213 6ec7a50e Iustin Pop
  my_pid <- getProcessID
214 6ec7a50e Iustin Pop
  _ <- fdWrite fd (show my_pid ++ "\n")
215 6ec7a50e Iustin Pop
  return fd
216 6ec7a50e Iustin Pop
217 79ac58fa Iustin Pop
-- | Helper to format an IOError.
218 79ac58fa Iustin Pop
formatIOError :: String -> IOError -> String
219 79ac58fa Iustin Pop
formatIOError msg err = msg ++ ": " ++  show err
220 79ac58fa Iustin Pop
221 6ec7a50e Iustin Pop
-- | Wrapper over '_writePidFile' that transforms IO exceptions into a
222 6ec7a50e Iustin Pop
-- 'Bad' value.
223 6ec7a50e Iustin Pop
writePidFile :: FilePath -> IO (Result Fd)
224 6ec7a50e Iustin Pop
writePidFile path = do
225 1251817b Iustin Pop
  Control.Exception.catch
226 1251817b Iustin Pop
    (fmap Ok $ _writePidFile path)
227 79ac58fa Iustin Pop
    (return . Bad . formatIOError "Failure during writing of the pid file")
228 6ec7a50e Iustin Pop
229 6ec7a50e Iustin Pop
-- | Sets up a daemon's environment.
230 6ec7a50e Iustin Pop
setupDaemonEnv :: FilePath -> FileMode -> IO ()
231 6ec7a50e Iustin Pop
setupDaemonEnv cwd umask = do
232 6ec7a50e Iustin Pop
  changeWorkingDirectory cwd
233 6ec7a50e Iustin Pop
  _ <- setFileCreationMask umask
234 6ec7a50e Iustin Pop
  _ <- createSession
235 6ec7a50e Iustin Pop
  return ()
236 6ec7a50e Iustin Pop
237 36691f08 Iustin Pop
-- | Signal handler for reopening log files.
238 36691f08 Iustin Pop
handleSigHup :: FilePath -> IO ()
239 36691f08 Iustin Pop
handleSigHup path = do
240 36691f08 Iustin Pop
  setupDaemonFDs (Just path)
241 36691f08 Iustin Pop
  logInfo "Reopening log files after receiving SIGHUP"
242 36691f08 Iustin Pop
243 0c28bee1 Iustin Pop
-- | Sets up a daemon's standard file descriptors.
244 0c28bee1 Iustin Pop
setupDaemonFDs :: Maybe FilePath -> IO ()
245 0c28bee1 Iustin Pop
setupDaemonFDs logfile = do
246 0c28bee1 Iustin Pop
  null_in_handle <- openFile devNull ReadMode
247 0c28bee1 Iustin Pop
  null_out_handle <- openFile (fromMaybe devNull logfile) AppendMode
248 0c28bee1 Iustin Pop
  hDuplicateTo null_in_handle stdin
249 0c28bee1 Iustin Pop
  hDuplicateTo null_out_handle stdout
250 0c28bee1 Iustin Pop
  hDuplicateTo null_out_handle stderr
251 0c28bee1 Iustin Pop
  hClose null_in_handle
252 0c28bee1 Iustin Pop
  hClose null_out_handle
253 0c28bee1 Iustin Pop
254 152e05e1 Iustin Pop
-- | Computes the default bind address for a given family.
255 152e05e1 Iustin Pop
defaultBindAddr :: Int                  -- ^ The port we want
256 152e05e1 Iustin Pop
                -> Socket.Family        -- ^ The cluster IP family
257 152e05e1 Iustin Pop
                -> Result (Socket.Family, Socket.SockAddr)
258 152e05e1 Iustin Pop
defaultBindAddr port Socket.AF_INET =
259 152e05e1 Iustin Pop
  Ok $ (Socket.AF_INET,
260 152e05e1 Iustin Pop
        Socket.SockAddrInet (fromIntegral port) Socket.iNADDR_ANY)
261 152e05e1 Iustin Pop
defaultBindAddr port Socket.AF_INET6 =
262 152e05e1 Iustin Pop
  Ok $ (Socket.AF_INET6,
263 152e05e1 Iustin Pop
        Socket.SockAddrInet6 (fromIntegral port) 0 Socket.iN6ADDR_ANY 0)
264 152e05e1 Iustin Pop
defaultBindAddr _ fam = Bad $ "Unsupported address family: " ++ show fam
265 152e05e1 Iustin Pop
266 152e05e1 Iustin Pop
-- | Default hints for the resolver
267 152e05e1 Iustin Pop
resolveAddrHints :: Maybe Socket.AddrInfo
268 152e05e1 Iustin Pop
resolveAddrHints =
269 152e05e1 Iustin Pop
  Just Socket.defaultHints { Socket.addrFlags = [Socket.AI_NUMERICHOST,
270 152e05e1 Iustin Pop
                                                 Socket.AI_NUMERICSERV] }
271 152e05e1 Iustin Pop
272 152e05e1 Iustin Pop
-- | Resolves a numeric address.
273 152e05e1 Iustin Pop
resolveAddr :: Int -> String -> IO (Result (Socket.Family, Socket.SockAddr))
274 152e05e1 Iustin Pop
resolveAddr port str = do
275 152e05e1 Iustin Pop
  resolved <- Socket.getAddrInfo resolveAddrHints (Just str) (Just (show port))
276 152e05e1 Iustin Pop
  return $ case resolved of
277 152e05e1 Iustin Pop
             [] -> Bad "Invalid results from lookup?"
278 152e05e1 Iustin Pop
             best:_ -> Ok $ (Socket.addrFamily best, Socket.addrAddress best)
279 152e05e1 Iustin Pop
280 152e05e1 Iustin Pop
-- | Based on the options, compute the socket address to use for the
281 152e05e1 Iustin Pop
-- daemon.
282 152e05e1 Iustin Pop
parseAddress :: DaemonOptions      -- ^ Command line options
283 152e05e1 Iustin Pop
             -> Int                -- ^ Default port for this daemon
284 152e05e1 Iustin Pop
             -> IO (Result (Socket.Family, Socket.SockAddr))
285 152e05e1 Iustin Pop
parseAddress opts defport = do
286 152e05e1 Iustin Pop
  let port = maybe defport fromIntegral $ optPort opts
287 152e05e1 Iustin Pop
  def_family <- Ssconf.getPrimaryIPFamily Nothing
288 152e05e1 Iustin Pop
  ainfo <- case optBindAddress opts of
289 152e05e1 Iustin Pop
             Nothing -> return (def_family >>= defaultBindAddr port)
290 1251817b Iustin Pop
             Just saddr -> Control.Exception.catch
291 1251817b Iustin Pop
                             (resolveAddr port saddr)
292 1251817b Iustin Pop
                             (annotateIOError $ "Invalid address " ++ saddr)
293 152e05e1 Iustin Pop
  return ainfo
294 152e05e1 Iustin Pop
295 6ec7a50e Iustin Pop
-- | Run an I/O action as a daemon.
296 6ec7a50e Iustin Pop
--
297 6ec7a50e Iustin Pop
-- WARNING: this only works in single-threaded mode (either using the
298 6ec7a50e Iustin Pop
-- single-threaded runtime, or using the multi-threaded one but with
299 6ec7a50e Iustin Pop
-- only one OS thread, i.e. -N1).
300 6ec7a50e Iustin Pop
--
301 6ec7a50e Iustin Pop
-- FIXME: this doesn't support error reporting and the prepfn
302 6ec7a50e Iustin Pop
-- functionality.
303 0c28bee1 Iustin Pop
daemonize :: FilePath -> IO () -> IO ()
304 0c28bee1 Iustin Pop
daemonize logfile action = do
305 6ec7a50e Iustin Pop
  -- first fork
306 6ec7a50e Iustin Pop
  _ <- forkProcess $ do
307 6ec7a50e Iustin Pop
    -- in the child
308 6ec7a50e Iustin Pop
    setupDaemonEnv "/" (unionFileModes groupModes otherModes)
309 0c28bee1 Iustin Pop
    setupDaemonFDs $ Just logfile
310 36691f08 Iustin Pop
    _ <- installHandler lostConnection (Catch (handleSigHup logfile)) Nothing
311 6ec7a50e Iustin Pop
    _ <- forkProcess action
312 6ec7a50e Iustin Pop
    exitImmediately ExitSuccess
313 6ec7a50e Iustin Pop
  exitImmediately ExitSuccess
314 6ec7a50e Iustin Pop
315 6ec7a50e Iustin Pop
-- | Generic daemon startup.
316 6ec7a50e Iustin Pop
genericMain :: GanetiDaemon -> [OptType] -> (DaemonOptions -> IO ()) -> IO ()
317 6ec7a50e Iustin Pop
genericMain daemon options main = do
318 6ec7a50e Iustin Pop
  let progname = daemonName daemon
319 6ec7a50e Iustin Pop
  (opts, args) <- parseArgs progname options
320 6ec7a50e Iustin Pop
321 6ec7a50e Iustin Pop
  when (optShowHelp opts) $ do
322 6ec7a50e Iustin Pop
    putStr $ usageHelp progname options
323 6ec7a50e Iustin Pop
    exitWith ExitSuccess
324 6ec7a50e Iustin Pop
  when (optShowVer opts) $ do
325 6ec7a50e Iustin Pop
    printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
326 6ec7a50e Iustin Pop
           progname Version.version
327 6ec7a50e Iustin Pop
           compilerName (Data.Version.showVersion compilerVersion)
328 6ec7a50e Iustin Pop
           os arch :: IO ()
329 6ec7a50e Iustin Pop
    exitWith ExitSuccess
330 88a10df5 Iustin Pop
331 88a10df5 Iustin Pop
  exitUnless (null args) "This program doesn't take any arguments"
332 6ec7a50e Iustin Pop
333 6ec7a50e Iustin Pop
  unless (optNoUserChecks opts) $ do
334 6ec7a50e Iustin Pop
    runtimeEnts <- getEnts
335 88a10df5 Iustin Pop
    ents <- exitIfBad "Can't find required user/groups" runtimeEnts
336 88a10df5 Iustin Pop
    verifyDaemonUser daemon ents
337 6ec7a50e Iustin Pop
338 b714ff89 Iustin Pop
  syslog <- case optSyslogUsage opts of
339 88a10df5 Iustin Pop
              Nothing -> exitIfBad "Invalid cluster syslog setting" $
340 b714ff89 Iustin Pop
                         syslogUsageFromRaw C.syslogUsage
341 b714ff89 Iustin Pop
              Just v -> return v
342 0c28bee1 Iustin Pop
  let processFn = if optDaemonize opts
343 0c28bee1 Iustin Pop
                    then daemonize (daemonLogFile daemon)
344 0c28bee1 Iustin Pop
                    else id
345 b714ff89 Iustin Pop
  processFn $ innerMain daemon opts syslog (main opts)
346 6ec7a50e Iustin Pop
347 6ec7a50e Iustin Pop
-- | Inner daemon function.
348 6ec7a50e Iustin Pop
--
349 6ec7a50e Iustin Pop
-- This is executed after daemonization.
350 b714ff89 Iustin Pop
innerMain :: GanetiDaemon -> DaemonOptions -> SyslogUsage -> IO () -> IO ()
351 b714ff89 Iustin Pop
innerMain daemon opts syslog main = do
352 0c28bee1 Iustin Pop
  let logfile = if optDaemonize opts
353 0c28bee1 Iustin Pop
                  then Nothing
354 0c28bee1 Iustin Pop
                  else Just $ daemonLogFile daemon
355 0c28bee1 Iustin Pop
  setupLogging logfile (daemonName daemon) (optDebug opts) True False syslog
356 6ec7a50e Iustin Pop
  pid_fd <- writePidFile (daemonPidFile daemon)
357 88a10df5 Iustin Pop
  _ <- exitIfBad "Cannot write PID file; already locked? Error" pid_fd
358 6ec7a50e Iustin Pop
  logNotice "starting"
359 6ec7a50e Iustin Pop
  main