Enable hbal to use the new command line option
[ganeti-local] / hbal.hs
diff --git a/hbal.hs b/hbal.hs
index 3ac9e78..529a643 100644 (file)
--- a/hbal.hs
+++ b/hbal.hs
@@ -25,6 +25,8 @@ Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
 
 module Main (main) where
 
+import Control.Concurrent (threadDelay)
+import Control.Exception (bracket)
 import Data.List
 import Data.Function
 import Data.Maybe (isJust, fromJust)
@@ -34,25 +36,34 @@ import System.IO
 import qualified System
 
 import Text.Printf (printf, hPrintf)
+import Text.JSON (showJSON)
 
 import qualified Ganeti.HTools.Container as Container
 import qualified Ganeti.HTools.Cluster as Cluster
 import qualified Ganeti.HTools.Node as Node
+import qualified Ganeti.HTools.Instance as Instance
 
 import Ganeti.HTools.CLI
 import Ganeti.HTools.ExtLoader
 import Ganeti.HTools.Utils
+import Ganeti.HTools.Types
+
+import qualified Ganeti.Luxi as L
+import qualified Ganeti.OpCodes as OpCodes
+import Ganeti.Jobs
 
 -- | Options list and functions
 options :: [OptType]
 options =
     [ oPrintNodes
+    , oPrintInsts
     , oPrintCommands
     , oOneline
-    , oNodeFile
-    , oInstFile
+    , oDataFile
+    , oEvacMode
     , oRapiMaster
     , oLuxiSocket
+    , oExecJobs
     , oMaxSolLength
     , oVerbose
     , oQuiet
@@ -61,6 +72,9 @@ options =
     , oMaxCpu
     , oMinDisk
     , oDiskMoves
+    , oDynuFile
+    , oExTags
+    , oExInst
     , oShowVer
     , oShowHelp
     ]
@@ -74,15 +88,19 @@ iterateDepth :: Cluster.Table    -- ^ The starting table
              -> Bool             -- ^ Allow disk moves
              -> Int              -- ^ Max node name len
              -> Int              -- ^ Max instance name len
-             -> [[String]]       -- ^ Current command list
+             -> [MoveJob]        -- ^ Current command list
              -> Bool             -- ^ Whether to be silent
-             -> Cluster.Score    -- ^ Score at which to stop
-             -> IO (Cluster.Table, [[String]]) -- ^ The resulting table and
-                                               -- commands
+             -> Score            -- ^ Score at which to stop
+             -> Bool             -- ^ Enable evacuation mode
+             -> IO (Cluster.Table, [MoveJob]) -- ^ The resulting table
+                                              -- and commands
 iterateDepth ini_tbl max_rounds disk_moves nmlen imlen
-             cmd_strs oneline min_score =
+             cmd_strs oneline min_score evac_mode =
     let Cluster.Table ini_nl ini_il _ _ = ini_tbl
-        m_fin_tbl = Cluster.tryBalance ini_tbl max_rounds disk_moves min_score
+        allowed_next = Cluster.doNextBalance ini_tbl max_rounds min_score
+        m_fin_tbl = if allowed_next
+                    then Cluster.tryBalance ini_tbl disk_moves evac_mode
+                    else Nothing
     in
       case m_fin_tbl of
         Just fin_tbl ->
@@ -90,14 +108,17 @@ iterateDepth ini_tbl max_rounds disk_moves nmlen imlen
               let
                   (Cluster.Table _ _ _ fin_plc) = fin_tbl
                   fin_plc_len = length fin_plc
+                  cur_plc@(idx, _, _, move, _) = head fin_plc
                   (sol_line, cmds) = Cluster.printSolutionLine ini_nl ini_il
-                                     nmlen imlen (head fin_plc) fin_plc_len
-                  upd_cmd_strs = cmds:cmd_strs
+                                     nmlen imlen cur_plc fin_plc_len
+                  afn = Cluster.involvedNodes ini_il cur_plc
+                  upd_cmd_strs = (afn, idx, move, cmds):cmd_strs
               unless oneline $ do
                        putStrLn sol_line
                        hFlush stdout
               iterateDepth fin_tbl max_rounds disk_moves
                            nmlen imlen upd_cmd_strs oneline min_score
+                           evac_mode
         Nothing -> return (ini_tbl, cmd_strs)
 
 -- | Formats the solution for the oneline display
@@ -106,6 +127,58 @@ formatOneline ini_cv plc_len fin_cv =
     printf "%.8f %d %.8f %8.3f" ini_cv plc_len fin_cv
                (if fin_cv == 0 then 1 else ini_cv / fin_cv)
 
+-- | Submits a list of jobs and waits for all to finish execution
+execJobs :: L.Client -> [[OpCodes.OpCode]] -> IO (Result [String])
+execJobs client = L.submitManyJobs client . showJSON
+
+-- | Polls a set of jobs at a fixed interval until all are finished
+-- one way or another
+waitForJobs :: L.Client -> [String] -> IO (Result [JobStatus])
+waitForJobs client jids = do
+  sts <- L.queryJobsStatus client jids
+  case sts of
+    Bad x -> return $ Bad x
+    Ok s -> if any (<= JobRunning) s
+            then do
+              -- TODO: replace hardcoded value with a better thing
+              threadDelay (1000000 * 15)
+              waitForJobs client jids
+            else return $ Ok s
+
+-- | Check that a set of job statuses is all success
+checkJobsStatus :: [JobStatus] -> Bool
+checkJobsStatus = all (== JobSuccess)
+
+-- | Execute an entire jobset
+execJobSet :: String -> String -> Node.List
+           -> Instance.List -> [JobSet] -> IO ()
+execJobSet _      _   _  _  [] = return ()
+execJobSet master csf nl il (js:jss) = do
+  -- map from jobset (htools list of positions) to [[opcodes]]
+  let jobs = map (\(_, idx, move, _) ->
+                      Cluster.iMoveToJob csf nl il idx move) js
+  let descr = map (\(_, idx, _, _) -> Container.nameOf il idx) js
+  putStrLn $ "Executing jobset for instances " ++ commaJoin descr
+  jrs <- bracket (L.getClient master) L.closeClient
+         (\client -> do
+            jids <- execJobs client jobs
+            case jids of
+              Bad x -> return $ Bad x
+              Ok x -> do
+                putStrLn $ "Got job IDs " ++ commaJoin x
+                waitForJobs client x
+         )
+  (case jrs of
+     Bad x -> do
+       hPutStrLn stderr $ "Cannot compute job status, aborting: " ++ show x
+       return ()
+     Ok x -> if checkJobsStatus x
+             then execJobSet master csf nl il jss
+             else do
+               hPutStrLn stderr $ "Not all jobs completed successfully: " ++
+                         show x
+               hPutStrLn stderr "Aborting.")
+
 -- | Main function.
 main :: IO ()
 main = do
@@ -118,8 +191,9 @@ main = do
 
   let oneline = optOneline opts
       verbose = optVerbose opts
+      shownodes = optShowNodes opts
 
-  (fixed_nl, il, csf) <- loadExternalData opts
+  (fixed_nl, il, ctags, csf) <- loadExternalData opts
 
   let offline_names = optOffline opts
       all_nodes = Container.elems fixed_nl
@@ -142,6 +216,9 @@ main = do
       nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
            nm
 
+  when (not oneline && verbose > 1) $
+       putStrLn $ "Loaded cluster tags: " ++ intercalate "," ctags
+
   when (Container.size il == 0) $ do
          (if oneline then putStrLn $ formatOneline 0 0 0
           else printf "Cluster is empty, exiting.\n")
@@ -163,10 +240,15 @@ main = do
          putStrLn "Cluster is not N+1 happy, continuing but no guarantee \
                   \that the cluster will end N+1 happy."
 
-  when (optShowNodes opts) $
+  when (optShowInsts opts) $ do
+         putStrLn ""
+         putStrLn "Initial instance map:"
+         putStrLn $ Cluster.printInsts nl il
+
+  when (isJust shownodes) $
        do
          putStrLn "Initial cluster status:"
-         putStrLn $ Cluster.printNodes nl
+         putStrLn $ Cluster.printNodes nl (fromJust shownodes)
 
   let ini_cv = Cluster.compCV nl
       ini_tbl = Cluster.Table nl il ini_cv []
@@ -192,8 +274,8 @@ main = do
 
   (fin_tbl, cmd_strs) <- iterateDepth ini_tbl (optMaxLength opts)
                          (optDiskMoves opts)
-                         nmlen imlen [] oneline min_cv
-  let (Cluster.Table fin_nl _ fin_cv fin_plc) = fin_tbl
+                         nmlen imlen [] oneline min_cv (optEvacMode opts)
+  let (Cluster.Table fin_nl fin_il fin_cv fin_plc) = fin_tbl
       ord_plc = reverse fin_plc
       sol_msg = if null fin_plc
                 then printf "No solution found\n"
@@ -209,7 +291,8 @@ main = do
   unless (oneline || verbose == 0) $
          printf "Solution length=%d\n" (length ord_plc)
 
-  let cmd_data = Cluster.formatCmds . reverse $ cmd_strs
+  let cmd_jobs = Cluster.splitJobs cmd_strs
+      cmd_data = Cluster.formatCmds cmd_jobs
 
   when (isJust $ optShowCmds opts) $
        do
@@ -218,24 +301,36 @@ main = do
          (if out_path == "-" then
               printf "Commands to run to reach the above solution:\n%s"
                      (unlines . map ("  " ++) .
-                      filter (/= "check") .
+                      filter (/= "  check") .
                       lines $ cmd_data)
           else do
             writeFile out_path (shTemplate ++ cmd_data)
             printf "The commands have been written to file '%s'\n" out_path)
 
-  when (optShowNodes opts) $
+  when (optExecJobs opts && not (null ord_plc))
+           (case optLuxi opts of
+              Nothing -> do
+                hPutStrLn stderr "Execution of commands possible only on LUXI"
+                exitWith $ ExitFailure 1
+              Just master -> execJobSet master csf fin_nl il cmd_jobs)
+
+  when (optShowInsts opts) $ do
+         putStrLn ""
+         putStrLn "Final instance map:"
+         putStr $ Cluster.printInsts fin_nl fin_il
+
+  when (isJust shownodes) $
        do
          let ini_cs = Cluster.totalResources nl
              fin_cs = Cluster.totalResources fin_nl
          putStrLn ""
          putStrLn "Final cluster status:"
-         putStrLn $ Cluster.printNodes fin_nl
+         putStrLn $ Cluster.printNodes fin_nl (fromJust shownodes)
          when (verbose > 3) $
               do
                 printf "Original: mem=%d disk=%d\n"
-                       (Cluster.cs_fmem ini_cs) (Cluster.cs_fdsk ini_cs)
+                       (Cluster.csFmem ini_cs) (Cluster.csFdsk ini_cs)
                 printf "Final:    mem=%d disk=%d\n"
-                       (Cluster.cs_fmem fin_cs) (Cluster.cs_fdsk fin_cs)
+                       (Cluster.csFmem fin_cs) (Cluster.csFdsk fin_cs)
   when oneline $
          putStrLn $ formatOneline ini_cv (length ord_plc) fin_cv