Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Daemon.hs @ 8d2b6a12

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