Use the mingain options in the balancing algorithm
[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, fromJust)
32 import Monad
33 import System (exitWith, ExitCode(..))
34 import System.IO
35 import qualified System
36
37 import Text.Printf (printf, hPrintf)
38
39 import qualified Ganeti.HTools.Container as Container
40 import qualified Ganeti.HTools.Cluster as Cluster
41 import qualified Ganeti.HTools.Node as Node
42 import qualified Ganeti.HTools.Instance as Instance
43
44 import Ganeti.HTools.CLI
45 import Ganeti.HTools.ExtLoader
46 import Ganeti.HTools.Utils
47 import Ganeti.HTools.Types
48
49 import Ganeti.HTools.Text (serializeCluster)
50
51 import qualified Ganeti.Luxi as L
52 import Ganeti.Jobs
53
54 -- | Options list and functions
55 options :: [OptType]
56 options =
57     [ oPrintNodes
58     , oPrintInsts
59     , oPrintCommands
60     , oOneline
61     , oDataFile
62     , oEvacMode
63     , oRapiMaster
64     , oLuxiSocket
65     , oExecJobs
66     , oMaxSolLength
67     , oVerbose
68     , oQuiet
69     , oOfflineNode
70     , oMinScore
71     , oMaxCpu
72     , oMinDisk
73     , oMinGain
74     , oMinGainLim
75     , oDiskMoves
76     , oDynuFile
77     , oExTags
78     , oExInst
79     , oSaveCluster
80     , oShowVer
81     , oShowHelp
82     ]
83
84 {- | Start computing the solution at the given depth and recurse until
85 we find a valid solution or we exceed the maximum depth.
86
87 -}
88 iterateDepth :: Cluster.Table    -- ^ The starting table
89              -> Int              -- ^ Remaining length
90              -> Bool             -- ^ Allow disk moves
91              -> Int              -- ^ Max node name len
92              -> Int              -- ^ Max instance name len
93              -> [MoveJob]        -- ^ Current command list
94              -> Bool             -- ^ Whether to be silent
95              -> Score            -- ^ Score at which to stop
96              -> Score            -- ^ Min gain limit
97              -> Score            -- ^ Min score gain
98              -> Bool             -- ^ Enable evacuation mode
99              -> IO (Cluster.Table, [MoveJob]) -- ^ The resulting table
100                                               -- and commands
101 iterateDepth ini_tbl max_rounds disk_moves nmlen imlen
102              cmd_strs oneline min_score mg_limit min_gain evac_mode =
103     let Cluster.Table ini_nl ini_il _ _ = ini_tbl
104         allowed_next = Cluster.doNextBalance ini_tbl max_rounds min_score
105         m_fin_tbl = if allowed_next
106                     then Cluster.tryBalance ini_tbl disk_moves evac_mode
107                          mg_limit min_gain
108                     else Nothing
109     in
110       case m_fin_tbl of
111         Just fin_tbl ->
112             do
113               let
114                   (Cluster.Table _ _ _ fin_plc) = fin_tbl
115                   fin_plc_len = length fin_plc
116                   cur_plc@(idx, _, _, move, _) = head fin_plc
117                   (sol_line, cmds) = Cluster.printSolutionLine ini_nl ini_il
118                                      nmlen imlen cur_plc fin_plc_len
119                   afn = Cluster.involvedNodes ini_il cur_plc
120                   upd_cmd_strs = (afn, idx, move, cmds):cmd_strs
121               unless oneline $ do
122                        putStrLn sol_line
123                        hFlush stdout
124               iterateDepth fin_tbl max_rounds disk_moves
125                            nmlen imlen upd_cmd_strs oneline min_score
126                            mg_limit min_gain evac_mode
127         Nothing -> return (ini_tbl, cmd_strs)
128
129 -- | Formats the solution for the oneline display
130 formatOneline :: Double -> Int -> Double -> String
131 formatOneline ini_cv plc_len fin_cv =
132     printf "%.8f %d %.8f %8.3f" ini_cv plc_len fin_cv
133                (if fin_cv == 0 then 1 else ini_cv / fin_cv)
134
135 -- | Polls a set of jobs at a fixed interval until all are finished
136 -- one way or another
137 waitForJobs :: L.Client -> [String] -> IO (Result [JobStatus])
138 waitForJobs client jids = do
139   sts <- L.queryJobsStatus client jids
140   case sts of
141     Bad x -> return $ Bad x
142     Ok s -> if any (<= JOB_STATUS_RUNNING) s
143             then do
144               -- TODO: replace hardcoded value with a better thing
145               threadDelay (1000000 * 15)
146               waitForJobs client jids
147             else return $ Ok s
148
149 -- | Check that a set of job statuses is all success
150 checkJobsStatus :: [JobStatus] -> Bool
151 checkJobsStatus = all (== JOB_STATUS_SUCCESS)
152
153 -- | Execute an entire jobset
154 execJobSet :: String -> Node.List
155            -> Instance.List -> [JobSet] -> IO ()
156 execJobSet _      _  _  [] = return ()
157 execJobSet master nl il (js:jss) = do
158   -- map from jobset (htools list of positions) to [[opcodes]]
159   let jobs = map (\(_, idx, move, _) ->
160                       Cluster.iMoveToJob nl il idx move) js
161   let descr = map (\(_, idx, _, _) -> Container.nameOf il idx) js
162   putStrLn $ "Executing jobset for instances " ++ commaJoin descr
163   jrs <- bracket (L.getClient master) L.closeClient
164          (\client -> do
165             jids <- L.submitManyJobs client jobs
166             case jids of
167               Bad x -> return $ Bad x
168               Ok x -> do
169                 putStrLn $ "Got job IDs " ++ commaJoin x
170                 waitForJobs client x
171          )
172   (case jrs of
173      Bad x -> do
174        hPutStrLn stderr $ "Cannot compute job status, aborting: " ++ show x
175        return ()
176      Ok x -> if checkJobsStatus x
177              then execJobSet master nl il jss
178              else do
179                hPutStrLn stderr $ "Not all jobs completed successfully: " ++
180                          show x
181                hPutStrLn stderr "Aborting.")
182
183 -- | Main function.
184 main :: IO ()
185 main = do
186   cmd_args <- System.getArgs
187   (opts, args) <- parseOpts cmd_args "hbal" options
188
189   unless (null args) $ do
190          hPutStrLn stderr "Error: this program doesn't take any arguments."
191          exitWith $ ExitFailure 1
192
193   let oneline = optOneline opts
194       verbose = optVerbose opts
195       shownodes = optShowNodes opts
196
197   (fixed_nl, il, ctags) <- loadExternalData opts
198
199   let offline_names = optOffline opts
200       all_nodes = Container.elems fixed_nl
201       all_names = concatMap allNames all_nodes
202       offline_wrong = filter (`notElem` all_names) offline_names
203       offline_indices = map Node.idx $
204                         filter (\n ->
205                                  Node.name n `elem` offline_names ||
206                                  Node.alias n `elem` offline_names)
207                                all_nodes
208       m_cpu = optMcpu opts
209       m_dsk = optMdsk opts
210       csf = commonSuffix fixed_nl il
211
212   when (length offline_wrong > 0) $ do
213          hPrintf stderr "Wrong node name(s) set as offline: %s\n"
214                      (commaJoin offline_wrong) :: IO ()
215          exitWith $ ExitFailure 1
216
217   let nm = Container.map (\n -> if Node.idx n `elem` offline_indices
218                                 then Node.setOffline n True
219                                 else n) fixed_nl
220       nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
221            nm
222
223   when (not oneline && verbose > 1) $
224        putStrLn $ "Loaded cluster tags: " ++ intercalate "," ctags
225
226   when (Container.size il == 0) $ do
227          (if oneline then putStrLn $ formatOneline 0 0 0
228           else printf "Cluster is empty, exiting.\n")
229          exitWith ExitSuccess
230
231   unless oneline $ printf "Loaded %d nodes, %d instances\n"
232              (Container.size nl)
233              (Container.size il)
234
235   when (length csf > 0 && not oneline && verbose > 1) $
236        printf "Note: Stripping common suffix of '%s' from names\n" csf
237
238   let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
239   unless (oneline || verbose == 0) $ printf
240              "Initial check done: %d bad nodes, %d bad instances.\n"
241              (length bad_nodes) (length bad_instances)
242
243   when (length bad_nodes > 0) $
244          putStrLn "Cluster is not N+1 happy, continuing but no guarantee \
245                   \that the cluster will end N+1 happy."
246
247   when (optShowInsts opts) $ do
248          putStrLn ""
249          putStrLn "Initial instance map:"
250          putStrLn $ Cluster.printInsts nl il
251
252   when (isJust shownodes) $
253        do
254          putStrLn "Initial cluster status:"
255          putStrLn $ Cluster.printNodes nl (fromJust shownodes)
256
257   let ini_cv = Cluster.compCV nl
258       ini_tbl = Cluster.Table nl il ini_cv []
259       min_cv = optMinScore opts
260
261   when (ini_cv < min_cv) $ do
262          (if oneline then
263               putStrLn $ formatOneline ini_cv 0 ini_cv
264           else printf "Cluster is already well balanced (initial score %.6g,\n\
265                       \minimum score %.6g).\nNothing to do, exiting\n"
266                       ini_cv min_cv)
267          exitWith ExitSuccess
268
269   unless oneline (if verbose > 2 then
270                       printf "Initial coefficients: overall %.8f, %s\n"
271                       ini_cv (Cluster.printStats nl)
272                   else
273                       printf "Initial score: %.8f\n" ini_cv)
274
275   unless oneline $ putStrLn "Trying to minimize the CV..."
276   let imlen = maximum . map (length . Instance.alias) $ Container.elems il
277       nmlen = maximum . map (length . Node.alias) $ Container.elems nl
278
279   (fin_tbl, cmd_strs) <- iterateDepth ini_tbl (optMaxLength opts)
280                          (optDiskMoves opts)
281                          nmlen imlen [] oneline min_cv
282                          (optMinGainLim opts) (optMinGain opts)
283                          (optEvacMode opts)
284   let (Cluster.Table fin_nl fin_il fin_cv fin_plc) = fin_tbl
285       ord_plc = reverse fin_plc
286       sol_msg = if null fin_plc
287                 then printf "No solution found\n"
288                 else if verbose > 2
289                      then printf "Final coefficients:   overall %.8f, %s\n"
290                           fin_cv (Cluster.printStats fin_nl)
291                      else printf "Cluster score improved from %.8f to %.8f\n"
292                           ini_cv fin_cv
293                               ::String
294
295   unless oneline $ putStr sol_msg
296
297   unless (oneline || verbose == 0) $
298          printf "Solution length=%d\n" (length ord_plc)
299
300   let cmd_jobs = Cluster.splitJobs cmd_strs
301       cmd_data = Cluster.formatCmds cmd_jobs
302
303   when (isJust $ optShowCmds opts) $
304        do
305          let out_path = fromJust $ optShowCmds opts
306          putStrLn ""
307          (if out_path == "-" then
308               printf "Commands to run to reach the above solution:\n%s"
309                      (unlines . map ("  " ++) .
310                       filter (/= "  check") .
311                       lines $ cmd_data)
312           else do
313             writeFile out_path (shTemplate ++ cmd_data)
314             printf "The commands have been written to file '%s'\n" out_path)
315
316   when (isJust $ optSaveCluster opts) $
317        do
318          let out_path = fromJust $ optSaveCluster opts
319              adata = serializeCluster fin_nl fin_il
320          writeFile out_path adata
321          printf "The cluster state has been written to file '%s'\n" out_path
322
323   when (optShowInsts opts) $ do
324          putStrLn ""
325          putStrLn "Final instance map:"
326          putStr $ Cluster.printInsts fin_nl fin_il
327
328   when (isJust shownodes) $
329        do
330          let ini_cs = Cluster.totalResources nl
331              fin_cs = Cluster.totalResources fin_nl
332          putStrLn ""
333          putStrLn "Final cluster status:"
334          putStrLn $ Cluster.printNodes fin_nl (fromJust shownodes)
335          when (verbose > 3) $
336               do
337                 printf "Original: mem=%d disk=%d\n"
338                        (Cluster.csFmem ini_cs) (Cluster.csFdsk ini_cs) :: IO ()
339                 printf "Final:    mem=%d disk=%d\n"
340                        (Cluster.csFmem fin_cs) (Cluster.csFdsk fin_cs)
341   when oneline $
342          putStrLn $ formatOneline ini_cv (length ord_plc) fin_cv
343
344   when (optExecJobs opts && not (null ord_plc))
345            (case optLuxi opts of
346               Nothing -> do
347                 hPutStrLn stderr "Execution of commands possible only on LUXI"
348                 exitWith $ ExitFailure 1
349               Just master -> execJobSet master fin_nl il cmd_jobs)