module Ganeti.Daemon
( DaemonOptions(..)
, OptType
, CheckFn
, PrepFn
, MainFn
, defaultOptions
, oShowHelp
, oShowVer
, oNoDaemonize
, oNoUserChecks
, oDebug
, oPort
, oBindAddress
, oSyslogUsage
, oForceNode
, oNoVoting
, oYesDoIt
, parseArgs
, parseAddress
, cleanupSocket
, describeError
, genericMain
, getFQDN
) where
import Control.Concurrent
import Control.Exception
import Control.Monad
import Data.Maybe (fromMaybe, listToMaybe)
import Text.Printf
import Data.Word
import GHC.IO.Handle (hDuplicateTo)
import Network.BSD (getHostName)
import qualified Network.Socket as Socket
import System.Console.GetOpt
import System.Directory
import System.Exit
import System.Environment
import System.IO
import System.IO.Error (isDoesNotExistError, modifyIOError, annotateIOError)
import System.Posix.Directory
import System.Posix.Files
import System.Posix.IO
import System.Posix.Process
import System.Posix.Types
import System.Posix.Signals
import Ganeti.Common as Common
import Ganeti.Logging
import Ganeti.Runtime
import Ganeti.BasicTypes
import Ganeti.Utils
import qualified Ganeti.Constants as C
import qualified Ganeti.Ssconf as Ssconf
devNull :: FilePath
devNull = "/dev/null"
daemonStartupErr :: String -> String
daemonStartupErr = ("Error when starting the daemon process: " ++)
data DaemonOptions = DaemonOptions
{ optShowHelp :: Bool
, optShowVer :: Bool
, optShowComp :: Bool
, optDaemonize :: Bool
, optPort :: Maybe Word16
, optDebug :: Bool
, optNoUserChecks :: Bool
, optBindAddress :: Maybe String
, optSyslogUsage :: Maybe SyslogUsage
, optForceNode :: Bool
, optNoVoting :: Bool
, optYesDoIt :: Bool
}
defaultOptions :: DaemonOptions
defaultOptions = DaemonOptions
{ optShowHelp = False
, optShowVer = False
, optShowComp = False
, optDaemonize = True
, optPort = Nothing
, optDebug = False
, optNoUserChecks = False
, optBindAddress = Nothing
, optSyslogUsage = Nothing
, optForceNode = False
, optNoVoting = False
, optYesDoIt = False
}
instance StandardOptions DaemonOptions where
helpRequested = optShowHelp
verRequested = optShowVer
compRequested = optShowComp
requestHelp o = o { optShowHelp = True }
requestVer o = o { optShowVer = True }
requestComp o = o { optShowComp = True }
type OptType = GenericOptType DaemonOptions
type CheckFn a = DaemonOptions -> IO (Either ExitCode a)
type PrepFn a b = DaemonOptions -> a -> IO b
type MainFn a b = DaemonOptions -> a -> b -> IO ()
oNoDaemonize :: OptType
oNoDaemonize =
(Option "f" ["foreground"]
(NoArg (\ opts -> Ok opts { optDaemonize = False }))
"Don't detach from the current terminal",
OptComplNone)
oDebug :: OptType
oDebug =
(Option "d" ["debug"]
(NoArg (\ opts -> Ok opts { optDebug = True }))
"Enable debug messages",
OptComplNone)
oNoUserChecks :: OptType
oNoUserChecks =
(Option "" ["no-user-checks"]
(NoArg (\ opts -> Ok opts { optNoUserChecks = True }))
"Ignore user checks",
OptComplNone)
oPort :: Int -> OptType
oPort def =
(Option "p" ["port"]
(reqWithConversion (tryRead "reading port")
(\port opts -> Ok opts { optPort = Just port }) "PORT")
("Network port (default: " ++ show def ++ ")"),
OptComplInteger)
oBindAddress :: OptType
oBindAddress =
(Option "b" ["bind"]
(ReqArg (\addr opts -> Ok opts { optBindAddress = Just addr })
"ADDR")
"Bind address (default depends on cluster configuration)",
OptComplInetAddr)
oSyslogUsage :: OptType
oSyslogUsage =
(Option "" ["syslog"]
(reqWithConversion syslogUsageFromRaw
(\su opts -> Ok opts { optSyslogUsage = Just su })
"SYSLOG")
("Enable logging to syslog (except debug \
\messages); one of 'no', 'yes' or 'only' [" ++ C.syslogUsage ++
"]"),
OptComplChoices ["yes", "no", "only"])
oForceNode :: OptType
oForceNode =
(Option "" ["force-node"]
(NoArg (\ opts -> Ok opts { optForceNode = True }))
"Force the daemon to run on a different node than the master",
OptComplNone)
oNoVoting :: OptType
oNoVoting =
(Option "" ["no-voting"]
(NoArg (\ opts -> Ok opts { optNoVoting = True }))
"Skip node agreement check (dangerous)",
OptComplNone)
oYesDoIt :: OptType
oYesDoIt =
(Option "" ["yes-do-it"]
(NoArg (\ opts -> Ok opts { optYesDoIt = True }))
"Force a dangerous operation",
OptComplNone)
genericOpts :: [OptType]
genericOpts = [ oShowHelp
, oShowVer
, oShowComp
]
ioErrorToResult :: String -> IOError -> IO (Result a)
ioErrorToResult description exc =
return . Bad $ description ++ ": " ++ show exc
parseArgs :: String -> [OptType] -> IO (DaemonOptions, [String])
parseArgs cmd options = do
cmd_args <- getArgs
parseOpts defaultOptions cmd_args cmd (options ++ genericOpts) []
pidFileMode :: FileMode
pidFileMode = unionFileModes ownerReadMode ownerWriteMode
pidFileFlags :: OpenFileFlags
pidFileFlags = defaultFileFlags { noctty = True, trunc = False }
writePidFile :: FilePath -> IO Fd
writePidFile path = do
fd <- openFd path ReadWrite (Just pidFileMode) pidFileFlags
setLock fd (WriteLock, AbsoluteSeek, 0, 0)
my_pid <- getProcessID
_ <- fdWrite fd (show my_pid ++ "\n")
return fd
cleanupSocket :: FilePath -> IO ()
cleanupSocket socketPath =
catchJust (guard . isDoesNotExistError) (removeLink socketPath)
(const $ return ())
setupDaemonEnv :: FilePath -> FileMode -> IO ()
setupDaemonEnv cwd umask = do
changeWorkingDirectory cwd
_ <- setFileCreationMask umask
_ <- createSession
return ()
finalCleanup :: FilePath -> IO ()
finalCleanup = removeFile
handleSigTerm :: ThreadId -> IO ()
handleSigTerm mainTID =
Control.Exception.throwTo mainTID ExitSuccess
handleSigHup :: FilePath -> IO ()
handleSigHup path = do
setupDaemonFDs (Just path)
logInfo "Reopening log files after receiving SIGHUP"
setupDaemonFDs :: Maybe FilePath -> IO ()
setupDaemonFDs logfile = do
null_in_handle <- openFile devNull ReadMode
null_out_handle <- openFile (fromMaybe devNull logfile) AppendMode
hDuplicateTo null_in_handle stdin
hDuplicateTo null_out_handle stdout
hDuplicateTo null_out_handle stderr
hClose null_in_handle
hClose null_out_handle
defaultBindAddr :: Int
-> Socket.Family
-> Result (Socket.Family, Socket.SockAddr)
defaultBindAddr port Socket.AF_INET =
Ok (Socket.AF_INET,
Socket.SockAddrInet (fromIntegral port) Socket.iNADDR_ANY)
defaultBindAddr port Socket.AF_INET6 =
Ok (Socket.AF_INET6,
Socket.SockAddrInet6 (fromIntegral port) 0 Socket.iN6ADDR_ANY 0)
defaultBindAddr _ fam = Bad $ "Unsupported address family: " ++ show fam
parseAddress :: DaemonOptions
-> Int
-> IO (Result (Socket.Family, Socket.SockAddr))
parseAddress opts defport = do
let port = maybe defport fromIntegral $ optPort opts
def_family <- Ssconf.getPrimaryIPFamily Nothing
case optBindAddress opts of
Nothing -> return (def_family >>= defaultBindAddr port)
Just saddr -> Control.Exception.catch
(resolveAddr port saddr)
(ioErrorToResult $ "Invalid address " ++ saddr)
vClusterHostNameEnvVar :: String
vClusterHostNameEnvVar = "GANETI_HOSTNAME"
getFQDN' :: Maybe Socket.AddrInfo -> IO String
getFQDN' hints = do
hostname <- getHostName
addrInfos <- Socket.getAddrInfo hints (Just hostname) Nothing
let address = listToMaybe addrInfos >>= (Just . Socket.addrAddress)
case address of
Just a -> do
fqdn <- liftM fst $ Socket.getNameInfo [] True False a
return (fromMaybe hostname fqdn)
Nothing -> return hostname
getFQDNwithHints :: Maybe Socket.AddrInfo -> IO String
getFQDNwithHints hints = do
let ioErrorToNothing :: IOError -> IO (Maybe String)
ioErrorToNothing _ = return Nothing
vcluster_node <- Control.Exception.catch
(liftM Just (getEnv vClusterHostNameEnvVar))
ioErrorToNothing
case vcluster_node of
Just node_name -> return node_name
Nothing -> getFQDN' hints
getFQDN :: IO String
getFQDN = do
familyresult <- Ssconf.getPrimaryIPFamily Nothing
getFQDNwithHints
$ genericResult (const Nothing)
(\family -> Just $ Socket.defaultHints { Socket.addrFamily = family })
familyresult
isMaster :: IO Bool
isMaster = do
curNode <- getFQDN
masterNode <- Ssconf.getMasterNode Nothing
case masterNode of
Ok n -> return (curNode == n)
Bad _ -> return False
ensureNode :: GanetiDaemon -> DaemonOptions -> IO ()
ensureNode daemon opts = do
is_master <- isMaster
when (daemonOnlyOnMaster daemon
&& not is_master
&& not (optForceNode opts)) $ do
putStrLn "Not master, exiting."
exitWith (ExitFailure C.exitNotmaster)
describeError :: String -> Maybe Handle -> Maybe FilePath -> IO a -> IO a
describeError descr hndl fpath =
modifyIOError (\e -> annotateIOError e descr hndl fpath)
daemonize :: FilePath -> (Maybe Fd -> IO ()) -> IO ()
daemonize logfile action = do
(rpipe, wpipe) <- createPipe
_ <- forkProcess $ do
closeFd rpipe
let wpipe' = Just wpipe
setupDaemonEnv "/" (unionFileModes groupModes otherModes)
setupDaemonFDs (Just logfile) `Control.Exception.catch`
handlePrepErr False wpipe'
_ <- forkProcess (action wpipe')
exitImmediately ExitSuccess
closeFd wpipe
hndl <- fdToHandle rpipe
errors <- hGetContents hndl
ecode <- if null errors
then return ExitSuccess
else do
hPutStrLn stderr $ daemonStartupErr errors
return $ ExitFailure C.exitFailure
exitImmediately ecode
genericMain :: GanetiDaemon
-> [OptType]
-> CheckFn a
-> PrepFn a b
-> MainFn a b
-> IO ()
genericMain daemon options check_fn prep_fn exec_fn = do
let progname = daemonName daemon
(opts, args) <- parseArgs progname options
when (optDebug opts && daemon == GanetiLuxid) .
hPutStrLn stderr $
printf C.debugModeConfidentialityWarning (daemonName daemon)
ensureNode daemon opts
exitUnless (null args) "This program doesn't take any arguments"
unless (optNoUserChecks opts) $ do
runtimeEnts <- runResultT getEnts
ents <- exitIfBad "Can't find required user/groups" runtimeEnts
verifyDaemonUser daemon ents
syslog <- case optSyslogUsage opts of
Nothing -> exitIfBad "Invalid cluster syslog setting" $
syslogUsageFromRaw C.syslogUsage
Just v -> return v
log_file <- daemonLogFile daemon
check_result <- check_fn opts
check_result' <- case check_result of
Left code -> exitWith code
Right v -> return v
let processFn = if optDaemonize opts
then daemonize log_file
else \action -> action Nothing
_ <- installHandler lostConnection (Catch (handleSigHup log_file)) Nothing
processFn $ innerMain daemon opts syslog check_result' prep_fn exec_fn
fullPrep :: GanetiDaemon
-> DaemonOptions
-> SyslogUsage
-> a
-> PrepFn a b
-> IO (FilePath, b)
fullPrep daemon opts syslog check_result prep_fn = do
logfile <- if optDaemonize opts
then return Nothing
else liftM Just $ daemonLogFile daemon
pidfile <- daemonPidFile daemon
let dname = daemonName daemon
setupLogging logfile dname (optDebug opts) True False syslog
_ <- describeError "writing PID file; already locked?"
Nothing (Just pidfile) $ writePidFile pidfile
logNotice $ dname ++ " daemon startup"
prep_res <- prep_fn opts check_result
tid <- myThreadId
_ <- installHandler sigTERM (Catch $ handleSigTerm tid) Nothing
return (pidfile, prep_res)
innerMain :: GanetiDaemon
-> DaemonOptions
-> SyslogUsage
-> a
-> PrepFn a b
-> MainFn a b
-> Maybe Fd
-> IO ()
innerMain daemon opts syslog check_result prep_fn exec_fn fd = do
(pidFile, prep_result) <- fullPrep daemon opts syslog check_result prep_fn
`Control.Exception.catch` handlePrepErr True fd
maybeCloseFd fd
finally (exec_fn opts check_result prep_result) (finalCleanup pidFile)
handlePrepErr :: Bool -> Maybe Fd -> IOError -> IO a
handlePrepErr logging_setup fd err = do
let msg = show err
case fd of
Just fd' -> fdWrite fd' msg >> return ()
Nothing -> hPutStrLn stderr (daemonStartupErr msg)
when logging_setup $ logError msg
exitWith $ ExitFailure 1
maybeCloseFd :: Maybe Fd -> IO ()
maybeCloseFd Nothing = return ()
maybeCloseFd (Just fd) = closeFd fd