module Ganeti.HTools.Program.Hroller
( main
, options
, arguments
) where
import Control.Monad
import Data.List
import Data.Ord
import qualified Data.IntMap as IntMap
import qualified Ganeti.HTools.Container as Container
import qualified Ganeti.HTools.Node as Node
import qualified Ganeti.HTools.Group as Group
import Ganeti.Common
import Ganeti.HTools.CLI
import Ganeti.HTools.ExtLoader
import Ganeti.HTools.Graph
import Ganeti.HTools.Loader
import Ganeti.Utils
options :: IO [OptType]
options = do
luxi <- oLuxiSocket
return
[ luxi
, oRapiMaster
, oDataFile
, oIAllocSrc
, oOfflineNode
, oVerbose
, oQuiet
, oNoHeaders
, oSaveCluster
, oGroup
, oForce
]
arguments :: [ArgCompletion]
arguments = []
getStats :: [(String, ColorVertMap)] -> String
getStats colorings = snd . foldr helper (0,"") $ algBySize colorings
where algostat (algo, cmap) = algo ++ ": " ++ size cmap ++ grpsizes cmap
size cmap = show (IntMap.size cmap) ++ " "
grpsizes cmap =
"(" ++ commaJoin (map (show.length) (IntMap.elems cmap)) ++ ")"
algBySize = sortBy (flip (comparing (IntMap.size.snd)))
helper :: (String, ColorVertMap) -> (Int, String) -> (Int, String)
helper el (0, _) = ((IntMap.size.snd) el, algostat el)
helper el (old, str)
| old == elsize = (elsize, str ++ " TIE " ++ algostat el)
| otherwise = (elsize, str ++ " LOOSE " ++ algostat el)
where elsize = (IntMap.size.snd) el
filterOutput :: Maybe Group.Group -> [[Node.Node]] -> [[Node.Node]]
filterOutput g l =
let onlineOnly = filter (not . Node.offline)
hasGroup grp node = Node.group node == Group.idx grp
byGroupOnly Nothing xs = xs
byGroupOnly (Just grp) xs = filter (hasGroup grp) xs
nonNullOnly = filter (not . null)
in nonNullOnly (map (onlineOnly . byGroupOnly g) l)
masterLast :: [[Node.Node]] -> [[Node.Node]]
masterLast rebootgroups =
map (uncurry (++)) . uncurry (++) . partition (null . snd) $
map (partition (not . Node.isMaster)) rebootgroups
main :: Options -> [String] -> IO ()
main opts args = do
unless (null args) $ exitErr "This program doesn't take any arguments."
let verbose = optVerbose opts
maybeExit = if optForce opts then warn else exitErr
ini_cdata@(ClusterData gl fixed_nl ilf _ _) <- loadExternalData opts
let master_names = map Node.name . filter Node.isMaster . IntMap.elems $
fixed_nl
case master_names of
[] -> maybeExit "No master node found (maybe not supported by backend)."
[ _ ] -> return ()
_ -> exitErr $ "Found more than one master node: " ++ show master_names
nlf <- setNodeStatus opts fixed_nl
maybeSaveData (optSaveCluster opts) "original" "before hroller run" ini_cdata
wantedGroup <- case optGroup opts of
Nothing -> return Nothing
Just name -> case Container.findByName gl name of
Nothing -> exitErr "Cannot find target group."
Just grp -> return (Just grp)
nodeGraph <- case Node.mkNodeGraph nlf ilf of
Nothing -> exitErr "Cannot create node graph"
Just g -> return g
when (verbose > 2) . putStrLn $ "Node Graph: " ++ show nodeGraph
let colorAlgorithms = [ ("LF", colorLF)
, ("Dsatur", colorDsatur)
, ("Dcolor", colorDcolor)
]
colorings = map (\(v,a) -> (v,(colorVertMap.a) nodeGraph)) colorAlgorithms
smallestColoring =
(snd . minimumBy (comparing (IntMap.size . snd))) colorings
idToNode = (`Container.find` nlf)
nodesRebootGroups = map (map idToNode) $ IntMap.elems smallestColoring
outputRebootGroups = masterLast $
filterOutput wantedGroup nodesRebootGroups
outputRebootNames = map (map Node.name) outputRebootGroups
when (verbose > 1) . putStrLn $ getStats colorings
unless (optNoHeaders opts) $
putStrLn "'Node Reboot Groups'"
mapM_ (putStrLn . commaJoin) outputRebootNames