module Ganeti.Daemon.Utils
( verifyMaster
, handleMasterVerificationOptions
) where
import Control.Concurrent (threadDelay)
import Control.Monad (unless)
import Data.Either (rights)
import qualified Data.Foldable as F
import Data.List (partition)
import System.Exit (ExitCode(..))
import Ganeti.BasicTypes
import qualified Ganeti.Config as Config
import qualified Ganeti.Constants as C
import Ganeti.Daemon (getFQDN, DaemonOptions, optNoVoting, optYesDoIt)
import Ganeti.Logging
import Ganeti.Objects
import qualified Ganeti.Path as Path
import Ganeti.Rpc
verifyMasterVotes :: IO (Result Bool)
verifyMasterVotes = runResultT $ do
liftIO $ logDebug "Gathering votes for the master node"
myName <- liftIO getFQDN
liftIO . logDebug $ "My hostname is " ++ myName
conf_file <- liftIO Path.clusterConfFile
config <- mkResultT $ Config.loadConfig conf_file
let nodes = F.toList $ configNodes config
votes <- liftIO . executeRpcCall nodes $ RpcCallMasterNodeName
let (missing, valid) = partition (isLeft . snd) votes
noDataNodes = map (nodeName . fst) missing
validVotes = map rpcResultMasterNodeNameMaster . rights $ map snd valid
inFavor = length $ filter (== myName) validVotes
voters = length nodes
unknown = length missing
liftIO . unless (null noDataNodes) . logWarning
. (++) "No voting RPC result from " $ show noDataNodes
liftIO . logDebug . (++) "Valid votes: " $ show validVotes
if 2 * inFavor > voters
then return True
else if 2 * (inFavor + unknown) > voters
then return False
else fail $ "Voting cannot be won by " ++ myName
++ ", valid votes of " ++ show voters
++ " are " ++ show validVotes
verifyMaster :: Int -> IO (Result ())
verifyMaster retries = runResultT $ do
won <- mkResultT verifyMasterVotes
unless won $
if retries <= 0
then fail "Couldn't gather voting results of enough nodes"
else do
liftIO $ logDebug "Voting not final due to missing votes."
liftIO . threadDelay $ C.masterVotingRetryIntervall * 1000000
mkResultT $ verifyMaster (retries 1)
handleMasterVerificationOptions :: DaemonOptions -> IO (Either ExitCode ())
handleMasterVerificationOptions opts =
if optNoVoting opts
then if optYesDoIt opts
then return $ Right ()
else do
logError "The no-voting option is dangerous and cannot be\
\ given without providing yes-do-it as well."
return . Left $ ExitFailure C.exitFailure
else do
masterStatus <- verifyMaster C.masterVotingRetries
case masterStatus of
Bad s -> do
logError $ "Failed to verify master status: " ++ s
return . Left $ ExitFailure C.exitFailure
Ok _ -> return $ Right ()