Simulation backend: allow multiple node groups
[ganeti-local] / hbal.hs
1 {-| Cluster rebalancer
2
3 -}
4
5 {-
6
7 Copyright (C) 2009, 2010 Google Inc.
8
9 This program is free software; you can redistribute it and/or modify
10 it under the terms of the GNU General Public License as published by
11 the Free Software Foundation; either version 2 of the License, or
12 (at your option) any later version.
13
14 This program is distributed in the hope that it will be useful, but
15 WITHOUT ANY WARRANTY; without even the implied warranty of
16 MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 General Public License for more details.
18
19 You should have received a copy of the GNU General Public License
20 along with this program; if not, write to the Free Software
21 Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 02110-1301, USA.
23
24 -}
25
26 module Main (main) where
27
28 import Control.Concurrent (threadDelay)
29 import Control.Exception (bracket)
30 import Data.List
31 import Data.Maybe (isJust, isNothing, fromJust)
32 import Data.IORef
33 import Monad
34 import System (exitWith, ExitCode(..))
35 import System.IO
36 import System.Posix.Process
37 import System.Posix.Signals
38 import qualified System
39
40 import Text.Printf (printf, hPrintf)
41
42 import qualified Ganeti.HTools.Container as Container
43 import qualified Ganeti.HTools.Cluster as Cluster
44 import qualified Ganeti.HTools.Group as Group
45 import qualified Ganeti.HTools.Node as Node
46 import qualified Ganeti.HTools.Instance as Instance
47
48 import Ganeti.HTools.CLI
49 import Ganeti.HTools.ExtLoader
50 import Ganeti.HTools.Utils
51 import Ganeti.HTools.Types
52
53 import Ganeti.HTools.Text (serializeCluster)
54
55 import qualified Ganeti.Luxi as L
56 import Ganeti.Jobs
57
58 -- | Options list and functions
59 options :: [OptType]
60 options =
61     [ oPrintNodes
62     , oPrintInsts
63     , oPrintCommands
64     , oOneline
65     , oDataFile
66     , oEvacMode
67     , oRapiMaster
68     , oLuxiSocket
69     , oExecJobs
70     , oGroup
71     , oMaxSolLength
72     , oVerbose
73     , oQuiet
74     , oOfflineNode
75     , oMinScore
76     , oMaxCpu
77     , oMinDisk
78     , oMinGain
79     , oMinGainLim
80     , oDiskMoves
81     , oDynuFile
82     , oExTags
83     , oExInst
84     , oSaveCluster
85     , oShowVer
86     , oShowHelp
87     ]
88
89 {- | Start computing the solution at the given depth and recurse until
90 we find a valid solution or we exceed the maximum depth.
91
92 -}
93 iterateDepth :: Cluster.Table    -- ^ The starting table
94              -> Int              -- ^ Remaining length
95              -> Bool             -- ^ Allow disk moves
96              -> Int              -- ^ Max node name len
97              -> Int              -- ^ Max instance name len
98              -> [MoveJob]        -- ^ Current command list
99              -> Bool             -- ^ Whether to be silent
100              -> Score            -- ^ Score at which to stop
101              -> Score            -- ^ Min gain limit
102              -> Score            -- ^ Min score gain
103              -> Bool             -- ^ Enable evacuation mode
104              -> IO (Cluster.Table, [MoveJob]) -- ^ The resulting table
105                                               -- and commands
106 iterateDepth ini_tbl max_rounds disk_moves nmlen imlen
107              cmd_strs oneline min_score mg_limit min_gain evac_mode =
108     let Cluster.Table ini_nl ini_il _ _ = ini_tbl
109         allowed_next = Cluster.doNextBalance ini_tbl max_rounds min_score
110         m_fin_tbl = if allowed_next
111                     then Cluster.tryBalance ini_tbl disk_moves evac_mode
112                          mg_limit min_gain
113                     else Nothing
114     in
115       case m_fin_tbl of
116         Just fin_tbl ->
117             do
118               let
119                   (Cluster.Table _ _ _ fin_plc) = fin_tbl
120                   fin_plc_len = length fin_plc
121                   cur_plc@(idx, _, _, move, _) = head fin_plc
122                   (sol_line, cmds) = Cluster.printSolutionLine ini_nl ini_il
123                                      nmlen imlen cur_plc fin_plc_len
124                   afn = Cluster.involvedNodes ini_il cur_plc
125                   upd_cmd_strs = (afn, idx, move, cmds):cmd_strs
126               unless oneline $ do
127                        putStrLn sol_line
128                        hFlush stdout
129               iterateDepth fin_tbl max_rounds disk_moves
130                            nmlen imlen upd_cmd_strs oneline min_score
131                            mg_limit min_gain evac_mode
132         Nothing -> return (ini_tbl, cmd_strs)
133
134 -- | Formats the solution for the oneline display
135 formatOneline :: Double -> Int -> Double -> String
136 formatOneline ini_cv plc_len fin_cv =
137     printf "%.8f %d %.8f %8.3f" ini_cv plc_len fin_cv
138                (if fin_cv == 0 then 1 else ini_cv / fin_cv)
139
140 -- | Polls a set of jobs at a fixed interval until all are finished
141 -- one way or another
142 waitForJobs :: L.Client -> [String] -> IO (Result [JobStatus])
143 waitForJobs client jids = do
144   sts <- L.queryJobsStatus client jids
145   case sts of
146     Bad x -> return $ Bad x
147     Ok s -> if any (<= JOB_STATUS_RUNNING) s
148             then do
149               -- TODO: replace hardcoded value with a better thing
150               threadDelay (1000000 * 15)
151               waitForJobs client jids
152             else return $ Ok s
153
154 -- | Check that a set of job statuses is all success
155 checkJobsStatus :: [JobStatus] -> Bool
156 checkJobsStatus = all (== JOB_STATUS_SUCCESS)
157
158 -- | Wrapper over execJobSet checking for early termination
159 execWrapper :: String -> Node.List
160            -> Instance.List -> IORef Int -> [JobSet] -> IO Bool
161 execWrapper _      _  _  _    [] = return True
162 execWrapper master nl il cref alljss = do
163   cancel <- readIORef cref
164   (if cancel > 0
165    then do
166      hPrintf stderr "Exiting early due to user request, %d\
167                     \ jobset(s) remaining." (length alljss)::IO ()
168      return False
169    else execJobSet master nl il cref alljss)
170
171 -- | Execute an entire jobset
172 execJobSet :: String -> Node.List
173            -> Instance.List -> IORef Int -> [JobSet] -> IO Bool
174 execJobSet _      _  _  _    [] = return True
175 execJobSet master nl il cref (js:jss) = do
176   -- map from jobset (htools list of positions) to [[opcodes]]
177   let jobs = map (\(_, idx, move, _) ->
178                       Cluster.iMoveToJob nl il idx move) js
179   let descr = map (\(_, idx, _, _) -> Container.nameOf il idx) js
180   putStrLn $ "Executing jobset for instances " ++ commaJoin descr
181   jrs <- bracket (L.getClient master) L.closeClient
182          (\client -> do
183             jids <- L.submitManyJobs client jobs
184             case jids of
185               Bad x -> return $ Bad x
186               Ok x -> do
187                 putStrLn $ "Got job IDs " ++ commaJoin x
188                 waitForJobs client x
189          )
190   (case jrs of
191      Bad x -> do
192        hPutStrLn stderr $ "Cannot compute job status, aborting: " ++ show x
193        return False
194      Ok x -> if checkJobsStatus x
195              then execWrapper master nl il cref jss
196              else do
197                hPutStrLn stderr $ "Not all jobs completed successfully: " ++
198                          show x
199                hPutStrLn stderr "Aborting."
200                return False)
201
202 -- | Signal handler for graceful termination
203 hangleSigInt :: IORef Int -> IO ()
204 hangleSigInt cref = do
205   writeIORef cref 1
206   putStrLn ("Cancel request registered, will exit at" ++
207             " the end of the current job set...")
208
209 -- | Signal handler for immediate termination
210 hangleSigTerm :: IORef Int -> IO ()
211 hangleSigTerm cref = do
212   -- update the cref to 2, just for consistency
213   writeIORef cref 2
214   putStrLn "Double cancel request, exiting now..."
215   exitImmediately $ ExitFailure 2
216
217 runJobSet :: String -> Node.List -> Instance.List -> [JobSet] -> IO Bool
218 runJobSet master fin_nl il cmd_jobs = do
219   cref <- newIORef 0
220   mapM_ (\(hnd, sig) -> installHandler sig (Catch (hnd cref)) Nothing)
221     [(hangleSigTerm, softwareTermination), (hangleSigInt, keyboardSignal)]
222   execWrapper master fin_nl il cref cmd_jobs
223
224 -- | Main function.
225 main :: IO ()
226 main = do
227   cmd_args <- System.getArgs
228   (opts, args) <- parseOpts cmd_args "hbal" options
229
230   unless (null args) $ do
231          hPutStrLn stderr "Error: this program doesn't take any arguments."
232          exitWith $ ExitFailure 1
233
234   let oneline = optOneline opts
235       verbose = optVerbose opts
236       shownodes = optShowNodes opts
237
238   (gl, fixed_nl, ilf, ctags) <- loadExternalData opts
239
240   let offline_names = optOffline opts
241       all_nodes = Container.elems fixed_nl
242       all_names = concatMap allNames all_nodes
243       offline_wrong = filter (`notElem` all_names) offline_names
244       offline_indices = map Node.idx $
245                         filter (\n ->
246                                  Node.name n `elem` offline_names ||
247                                  Node.alias n `elem` offline_names)
248                                all_nodes
249       m_cpu = optMcpu opts
250       m_dsk = optMdsk opts
251       csf = commonSuffix fixed_nl ilf
252
253   when (length offline_wrong > 0) $ do
254          hPrintf stderr "Wrong node name(s) set as offline: %s\n"
255                      (commaJoin offline_wrong) :: IO ()
256          exitWith $ ExitFailure 1
257
258   let nm = Container.map (\n -> if Node.idx n `elem` offline_indices
259                                 then Node.setOffline n True
260                                 else n) fixed_nl
261       nlf = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
262             nm
263
264   when (not oneline && verbose > 1) $
265        putStrLn $ "Loaded cluster tags: " ++ intercalate "," ctags
266
267   when (Container.size ilf == 0) $ do
268          (if oneline then putStrLn $ formatOneline 0 0 0
269           else printf "Cluster is empty, exiting.\n")
270          exitWith ExitSuccess
271
272   let split_insts = Cluster.findSplitInstances nlf ilf
273   when (not . null $ split_insts) $ do
274     hPutStrLn stderr "Found instances belonging to multiple node groups:"
275     mapM_ (\i -> hPutStrLn stderr $ "  " ++ Instance.name i) split_insts
276     hPutStrLn stderr "Aborting."
277     exitWith $ ExitFailure 1
278
279   let ngroups = Cluster.splitCluster nlf ilf
280   when (length ngroups > 1 && isNothing (optGroup opts)) $ do
281     hPutStrLn stderr "Found multiple node groups:"
282     mapM_ (hPutStrLn stderr . ("  " ++) . Group.name .
283            (flip Container.find gl) . fst) ngroups
284     hPutStrLn stderr "Aborting."
285     exitWith $ ExitFailure 1
286
287   unless oneline $ printf "Loaded %d nodes, %d instances\n"
288              (Container.size nlf)
289              (Container.size ilf)
290
291   (gname, (nl, il)) <- case optGroup opts of
292     Nothing -> do
293          let (gidx, cdata) = head ngroups
294              grp = Container.find gidx gl
295          return (Group.name grp, cdata)
296     Just g -> case Container.findByName gl g of
297       Nothing -> do
298         hPutStrLn stderr $ "Node group " ++ g ++
299           " not found. Node group list is:"
300         mapM_ (hPutStrLn stderr . ("  " ++) . Group.name ) (Container.elems gl)
301         hPutStrLn stderr "Aborting."
302         exitWith $ ExitFailure 1
303       Just grp ->
304           case lookup (Group.idx grp) ngroups of
305             Nothing -> do
306               -- TODO: while this is unlikely to happen, log here the
307               -- actual group data to help debugging
308               hPutStrLn stderr $ "Internal failure, missing group idx"
309               exitWith $ ExitFailure 1
310             Just cdata -> return (Group.name grp, cdata)
311
312   unless oneline $ printf "Group size %d nodes, %d instances\n"
313              (Container.size nl)
314              (Container.size il)
315
316   putStrLn $ "Selected node group: " ++ gname
317
318   when (length csf > 0 && not oneline && verbose > 1) $
319        printf "Note: Stripping common suffix of '%s' from names\n" csf
320
321   let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
322   unless (oneline || verbose == 0) $ printf
323              "Initial check done: %d bad nodes, %d bad instances.\n"
324              (length bad_nodes) (length bad_instances)
325
326   when (length bad_nodes > 0) $
327          putStrLn "Cluster is not N+1 happy, continuing but no guarantee \
328                   \that the cluster will end N+1 happy."
329
330   when (optShowInsts opts) $ do
331          putStrLn ""
332          putStrLn "Initial instance map:"
333          putStrLn $ Cluster.printInsts nl il
334
335   when (isJust shownodes) $
336        do
337          putStrLn "Initial cluster status:"
338          putStrLn $ Cluster.printNodes nl (fromJust shownodes)
339
340   let ini_cv = Cluster.compCV nl
341       ini_tbl = Cluster.Table nl il ini_cv []
342       min_cv = optMinScore opts
343
344   when (ini_cv < min_cv) $ do
345          (if oneline then
346               putStrLn $ formatOneline ini_cv 0 ini_cv
347           else printf "Cluster is already well balanced (initial score %.6g,\n\
348                       \minimum score %.6g).\nNothing to do, exiting\n"
349                       ini_cv min_cv)
350          exitWith ExitSuccess
351
352   unless oneline (if verbose > 2 then
353                       printf "Initial coefficients: overall %.8f, %s\n"
354                       ini_cv (Cluster.printStats nl)
355                   else
356                       printf "Initial score: %.8f\n" ini_cv)
357
358   unless oneline $ putStrLn "Trying to minimize the CV..."
359   let imlen = maximum . map (length . Instance.alias) $ Container.elems il
360       nmlen = maximum . map (length . Node.alias) $ Container.elems nl
361
362   (fin_tbl, cmd_strs) <- iterateDepth ini_tbl (optMaxLength opts)
363                          (optDiskMoves opts)
364                          nmlen imlen [] oneline min_cv
365                          (optMinGainLim opts) (optMinGain opts)
366                          (optEvacMode opts)
367   let (Cluster.Table fin_nl fin_il fin_cv fin_plc) = fin_tbl
368       ord_plc = reverse fin_plc
369       sol_msg = if null fin_plc
370                 then printf "No solution found\n"
371                 else if verbose > 2
372                      then printf "Final coefficients:   overall %.8f, %s\n"
373                           fin_cv (Cluster.printStats fin_nl)
374                      else printf "Cluster score improved from %.8f to %.8f\n"
375                           ini_cv fin_cv
376                               ::String
377
378   unless oneline $ putStr sol_msg
379
380   unless (oneline || verbose == 0) $
381          printf "Solution length=%d\n" (length ord_plc)
382
383   let cmd_jobs = Cluster.splitJobs cmd_strs
384       cmd_data = Cluster.formatCmds cmd_jobs
385
386   when (isJust $ optShowCmds opts) $
387        do
388          let out_path = fromJust $ optShowCmds opts
389          putStrLn ""
390          (if out_path == "-" then
391               printf "Commands to run to reach the above solution:\n%s"
392                      (unlines . map ("  " ++) .
393                       filter (/= "  check") .
394                       lines $ cmd_data)
395           else do
396             writeFile out_path (shTemplate ++ cmd_data)
397             printf "The commands have been written to file '%s'\n" out_path)
398
399   when (isJust $ optSaveCluster opts) $
400        do
401          let out_path = fromJust $ optSaveCluster opts
402              adata = serializeCluster gl fin_nl fin_il ctags
403          writeFile out_path adata
404          printf "The cluster state has been written to file '%s'\n" out_path
405
406   when (optShowInsts opts) $ do
407          putStrLn ""
408          putStrLn "Final instance map:"
409          putStr $ Cluster.printInsts fin_nl fin_il
410
411   when (isJust shownodes) $
412        do
413          let ini_cs = Cluster.totalResources nl
414              fin_cs = Cluster.totalResources fin_nl
415          putStrLn ""
416          putStrLn "Final cluster status:"
417          putStrLn $ Cluster.printNodes fin_nl (fromJust shownodes)
418          when (verbose > 3) $
419               do
420                 printf "Original: mem=%d disk=%d\n"
421                        (Cluster.csFmem ini_cs) (Cluster.csFdsk ini_cs) :: IO ()
422                 printf "Final:    mem=%d disk=%d\n"
423                        (Cluster.csFmem fin_cs) (Cluster.csFdsk fin_cs)
424   when oneline $
425          putStrLn $ formatOneline ini_cv (length ord_plc) fin_cv
426
427   eval <-
428       if optExecJobs opts && not (null ord_plc)
429       then (case optLuxi opts of
430               Nothing -> do
431                 hPutStrLn stderr "Execution of commands possible only on LUXI"
432                 return False
433               Just master -> runJobSet master fin_nl il cmd_jobs)
434       else return True
435   when (not eval) (exitWith (ExitFailure 1))