X-Git-Url: https://code.grnet.gr/git/ganeti-local/blobdiff_plain/58709f9254a0daa44f76885fbfe94206aa8e1835..80276b9e18f3892d17af29d19829810a0f1f8341:/hail.hs diff --git a/hail.hs b/hail.hs index 92baae6..217c799 100644 --- a/hail.hs +++ b/hail.hs @@ -6,7 +6,7 @@ module Main (main) where import Data.List import Data.Function -import Data.Maybe (isJust, fromJust, fromMaybe) +import Data.Maybe (isJust, fromJust) import Monad import System import System.IO @@ -21,91 +21,29 @@ import qualified Ganeti.HTools.Node as Node import qualified Ganeti.HTools.Instance as Instance import qualified Ganeti.HTools.CLI as CLI import Ganeti.HTools.IAlloc -import Ganeti.HTools.Utils import Ganeti.HTools.Types -- | Command line options structure. data Options = Options - { optShowNodes :: Bool -- ^ Whether to show node status - , optShowCmds :: Maybe FilePath -- ^ Whether to show the command list - , optOneline :: Bool -- ^ Switch output to a single line - , optNodef :: FilePath -- ^ Path to the nodes file - , optNodeSet :: Bool -- ^ The nodes have been set by options - , optInstf :: FilePath -- ^ Path to the instances file - , optInstSet :: Bool -- ^ The insts have been set by options - , optMaxLength :: Int -- ^ Stop after this many steps - , optMaster :: String -- ^ Collect data from RAPI - , optVerbose :: Int -- ^ Verbosity level - , optOffline :: [String] -- ^ Names of offline nodes - , optMinScore :: Cluster.Score -- ^ The minimum score we aim for - , optShowVer :: Bool -- ^ Just show the program version + { optShowVer :: Bool -- ^ Just show the program version , optShowHelp :: Bool -- ^ Just show the help } deriving Show -instance CLI.CLIOptions Options where - showVersion = optShowVer - showHelp = optShowHelp - -- | Default values for the command line options. defaultOptions :: Options defaultOptions = Options - { optShowNodes = False - , optShowCmds = Nothing - , optOneline = False - , optNodef = "nodes" - , optNodeSet = False - , optInstf = "instances" - , optInstSet = False - , optMaxLength = -1 - , optMaster = "" - , optVerbose = 1 - , optOffline = [] - , optMinScore = 1e-9 - , optShowVer = False + { optShowVer = False , optShowHelp = False } +instance CLI.CLIOptions Options where + showVersion = optShowVer + showHelp = optShowHelp + -- | Options list and functions options :: [OptDescr (Options -> Options)] options = - [ Option ['p'] ["print-nodes"] - (NoArg (\ opts -> opts { optShowNodes = True })) - "print the final node list" - , Option ['C'] ["print-commands"] - (OptArg ((\ f opts -> opts { optShowCmds = Just f }) . fromMaybe "-") - "FILE") - "print the ganeti command list for reaching the solution,\ - \if an argument is passed then write the commands to a file named\ - \ as such" - , Option ['o'] ["oneline"] - (NoArg (\ opts -> opts { optOneline = True })) - "print the ganeti command list for reaching the solution" - , Option ['n'] ["nodes"] - (ReqArg (\ f opts -> opts { optNodef = f, optNodeSet = True }) "FILE") - "the node list FILE" - , Option ['i'] ["instances"] - (ReqArg (\ f opts -> opts { optInstf = f, optInstSet = True }) "FILE") - "the instance list FILE" - , Option ['m'] ["master"] - (ReqArg (\ m opts -> opts { optMaster = m }) "ADDRESS") - "collect data via RAPI at the given ADDRESS" - , Option ['l'] ["max-length"] - (ReqArg (\ i opts -> opts { optMaxLength = (read i)::Int }) "N") - "cap the solution at this many moves (useful for very unbalanced \ - \clusters)" - , Option ['v'] ["verbose"] - (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) + 1 })) - "increase the verbosity level" - , Option ['q'] ["quiet"] - (NoArg (\ opts -> opts { optVerbose = (optVerbose opts) - 1 })) - "decrease the verbosity level" - , Option ['O'] ["offline"] - (ReqArg (\ n opts -> opts { optOffline = n:optOffline opts }) "NODE") - " set node as offline" - , Option ['e'] ["min-score"] - (ReqArg (\ e opts -> opts { optMinScore = read e }) "EPSILON") - " mininum score to aim for" - , Option ['V'] ["version"] + [ Option ['V'] ["version"] (NoArg (\ opts -> opts { optShowVer = True})) "show the version of the program" , Option ['h'] ["help"] @@ -113,23 +51,46 @@ options = "show help" ] +-- | Compute online nodes from a NodeList +getOnline :: NodeList -> [Node.Node] +getOnline = filter (not . Node.offline) . Container.elems + -- | Try to allocate an instance on the cluster -tryAlloc :: NodeList +tryAlloc :: (Monad m) => + NodeList -> InstanceList -> Instance.Instance -> Int - -> Result (String, [Node.Node]) -tryAlloc nl il xi _ = Bad "alloc not implemented" + -> m [(Maybe NodeList, [Node.Node])] +tryAlloc nl _ inst 2 = + let all_nodes = getOnline nl + all_pairs = liftM2 (,) all_nodes all_nodes + ok_pairs = filter (\(x, y) -> Node.idx x /= Node.idx y) all_pairs + sols = map (\(p, s) -> + (fst $ Cluster.allocateOnPair nl inst p s, [p, s])) + ok_pairs + in return sols + +tryAlloc nl _ inst 1 = + let all_nodes = getOnline nl + sols = map (\p -> (fst $ Cluster.allocateOnSingle nl inst p, [p])) + all_nodes + in return sols + +tryAlloc _ _ _ reqn = fail $ "Unsupported number of alllocation \ + \destinations required (" ++ (show reqn) ++ + "), only two supported" -- | Try to allocate an instance on the cluster -tryReloc :: NodeList +tryReloc :: (Monad m) => + NodeList -> InstanceList -> Int -> Int -> [Int] - -> Result (String, [Node.Node]) + -> m [(Maybe NodeList, [Node.Node])] tryReloc nl il xid 1 ex_idx = - let all_nodes = Container.elems nl + let all_nodes = getOnline nl inst = Container.find xid il valid_nodes = filter (not . flip elem ex_idx . idx) all_nodes valid_idxes = map Node.idx valid_nodes @@ -139,39 +100,42 @@ tryReloc nl il xid 1 ex_idx = sols1 = map (\x -> let (mnl, _, _, _) = Cluster.applyMove nl' inst (Cluster.ReplaceSecondary x) - in (mnl, x) + in (mnl, [Container.find x nl']) ) valid_idxes - sols2 = filter (isJust . fst) sols1 - in if null sols1 then - Bad "No nodes onto which to relocate at all" - else if null sols2 then - Bad "No valid solutions" + in return sols1 + +tryReloc _ _ _ reqn _ = fail $ "Unsupported number of relocation \ + \destinations required (" ++ (show reqn) ++ + "), only one supported" + +filterFails :: (Monad m) => [(Maybe NodeList, [Node.Node])] + -> m [(NodeList, [Node.Node])] +filterFails sols = + if null sols then fail "No nodes onto which to allocate at all" + else let sols' = filter (isJust . fst) sols + in if null sols' then + fail "No valid allocation solutions" else - let sols3 = map (\(x, y) -> - (Cluster.compCV $ fromJust x, - (fromJust x, y))) - sols2 - sols4 = sortBy (compare `on` fst) sols3 - (best, (final_nl, winner)) = head sols4 - (worst, (_, loser)) = last sols4 - wnode = Container.find winner final_nl - lnode = Container.find loser nl - info = printf "Valid results: %d, best score: %.8f \ - \(node %s), worst score: %.8f (node %s)" - (length sols3) best (Node.name wnode) - worst (Node.name lnode) - in Ok (info, [wnode]) - -tryReloc _ _ _ reqn _ = Bad $ "Unsupported number of relocation \ - \destinations required (" ++ (show reqn) ++ - "), only one supported" + return $ map (\(x, y) -> (fromJust x, y)) sols' + +processResults :: (Monad m) => [(NodeList, [Node.Node])] + -> m (String, [Node.Node]) +processResults sols = + let sols' = map (\(nl', ns) -> (Cluster.compCV nl', ns)) sols + sols'' = sortBy (compare `on` fst) sols' + (best, w) = head sols'' + (worst, l) = last sols'' + info = printf "Valid results: %d, best score: %.8f for node(s) %s, \ + \worst score: %.8f for node(s) %s" (length sols'') + best (intercalate "/" . map Node.name $ w) + worst (intercalate "/" . map Node.name $ l) + in return (info, w) -- | Main function. main :: IO () main = do cmd_args <- System.getArgs - (opts, args) <- CLI.parseOpts cmd_args "hail" options - defaultOptions + (_, args) <- CLI.parseOpts cmd_args "hail" options defaultOptions when (null args) $ do hPutStrLn stderr "Error: this program needs an input file." @@ -191,9 +155,10 @@ main = do Allocate xi reqn -> tryAlloc nl il xi reqn Relocate idx reqn exnodes -> tryReloc nl il idx reqn exnodes - let (ok, info, rn) = case new_nodes of + let sols = new_nodes >>= filterFails >>= processResults + let (ok, info, rn) = case sols of Ok (info, sn) -> (True, "Request successful: " ++ info, - map name sn) + map ((++ csf) . name) sn) Bad s -> (False, "Request failed: " ++ s, []) resp = formatResponse ok info rn putStrLn resp