Fix a few hlint errors
[ganeti-local] / hbal.hs
1 {-| Cluster rebalancer
2
3 -}
4
5 {-
6
7 Copyright (C) 2009 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 Data.List
29 import Data.Function
30 import Data.Maybe (isJust, fromJust, fromMaybe)
31 import Monad
32 import System
33 import System.IO
34 import System.Console.GetOpt
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.CLI as CLI
43
44 import Ganeti.HTools.Utils
45
46 -- | Command line options structure.
47 data Options = Options
48     { optShowNodes :: Bool           -- ^ Whether to show node status
49     , optShowCmds  :: Maybe FilePath -- ^ Whether to show the command list
50     , optOneline   :: Bool           -- ^ Switch output to a single line
51     , optNodef     :: FilePath       -- ^ Path to the nodes file
52     , optNodeSet   :: Bool           -- ^ The nodes have been set by options
53     , optInstf     :: FilePath       -- ^ Path to the instances file
54     , optInstSet   :: Bool           -- ^ The insts have been set by options
55     , optMaxLength :: Int            -- ^ Stop after this many steps
56     , optMaster    :: String         -- ^ Collect data from RAPI
57     , optLuxi      :: Maybe FilePath -- ^ Collect data from Luxi
58     , optVerbose   :: Int            -- ^ Verbosity level
59     , optOffline   :: [String]       -- ^ Names of offline nodes
60     , optMinScore  :: Cluster.Score  -- ^ The minimum score we aim for
61     , optMcpu      :: Double         -- ^ Max cpu ratio for nodes
62     , optMdsk      :: Double         -- ^ Max disk usage ratio for nodes
63     , optShowVer   :: Bool           -- ^ Just show the program version
64     , optShowHelp  :: Bool           -- ^ Just show the help
65     } deriving Show
66
67 instance CLI.CLIOptions Options where
68     showVersion = optShowVer
69     showHelp    = optShowHelp
70
71 instance CLI.EToolOptions Options where
72     nodeFile   = optNodef
73     nodeSet    = optNodeSet
74     instFile   = optInstf
75     instSet    = optInstSet
76     masterName = optMaster
77     luxiSocket = optLuxi
78     silent a   = optVerbose a == 0
79
80 -- | Default values for the command line options.
81 defaultOptions :: Options
82 defaultOptions  = Options
83  { optShowNodes = False
84  , optShowCmds  = Nothing
85  , optOneline   = False
86  , optNodef     = "nodes"
87  , optNodeSet   = False
88  , optInstf     = "instances"
89  , optInstSet   = False
90  , optMaxLength = -1
91  , optMaster    = ""
92  , optLuxi      = Nothing
93  , optVerbose   = 1
94  , optOffline   = []
95  , optMinScore  = 1e-9
96  , optMcpu      = -1
97  , optMdsk      = -1
98  , optShowVer   = False
99  , optShowHelp  = False
100  }
101
102 -- | Options list and functions
103 options :: [OptDescr (Options -> Options)]
104 options =
105     [ Option ['p']     ["print-nodes"]
106       (NoArg (\ opts -> opts { optShowNodes = True }))
107       "print the final node list"
108     , Option ['C']     ["print-commands"]
109       (OptArg ((\ f opts -> opts { optShowCmds = Just f }) . fromMaybe "-")
110                   "FILE")
111       "print the ganeti command list for reaching the solution,\
112       \if an argument is passed then write the commands to a file named\
113       \ as such"
114     , Option ['o']     ["oneline"]
115       (NoArg (\ opts -> opts { optOneline = True }))
116       "print the ganeti command list for reaching the solution"
117     , Option ['n']     ["nodes"]
118       (ReqArg (\ f opts -> opts { optNodef = f, optNodeSet = True }) "FILE")
119       "the node list FILE"
120     , Option ['i']     ["instances"]
121       (ReqArg (\ f opts -> opts { optInstf =  f, optInstSet = True }) "FILE")
122       "the instance list FILE"
123     , Option ['m']     ["master"]
124       (ReqArg (\ m opts -> opts { optMaster = m }) "ADDRESS")
125       "collect data via RAPI at the given ADDRESS"
126     , Option ['L']     ["luxi"]
127       (OptArg ((\ f opts -> opts { optLuxi = Just f }) .
128                fromMaybe CLI.defaultLuxiSocket) "SOCKET")
129        "collect data via Luxi, optionally using the given SOCKET path"
130     , Option ['l']     ["max-length"]
131       (ReqArg (\ i opts -> opts { optMaxLength =  read i::Int }) "N")
132       "cap the solution at this many moves (useful for very unbalanced \
133       \clusters)"
134     , Option ['v']     ["verbose"]
135       (NoArg (\ opts -> opts { optVerbose = optVerbose opts + 1 }))
136       "increase the verbosity level"
137     , Option ['q']     ["quiet"]
138       (NoArg (\ opts -> opts { optVerbose = optVerbose opts - 1 }))
139       "decrease the verbosity level"
140     , Option ['O']     ["offline"]
141       (ReqArg (\ n opts -> opts { optOffline = n:optOffline opts }) "NODE")
142       " set node as offline"
143     , Option ['e']     ["min-score"]
144       (ReqArg (\ e opts -> opts { optMinScore = read e }) "EPSILON")
145       " mininum score to aim for"
146     , Option []        ["max-cpu"]
147       (ReqArg (\ n opts -> opts { optMcpu = read n }) "RATIO")
148       "maximum virtual-to-physical cpu ratio for nodes"
149     , Option []        ["min-disk"]
150       (ReqArg (\ n opts -> opts { optMdsk = read n }) "RATIO")
151       "minimum free disk space for nodes (between 0 and 1)"
152     , Option ['V']     ["version"]
153       (NoArg (\ opts -> opts { optShowVer = True}))
154       "show the version of the program"
155     , Option ['h']     ["help"]
156       (NoArg (\ opts -> opts { optShowHelp = True}))
157       "show help"
158     ]
159
160 {- | Start computing the solution at the given depth and recurse until
161 we find a valid solution or we exceed the maximum depth.
162
163 -}
164 iterateDepth :: Cluster.Table    -- ^ The starting table
165              -> Int              -- ^ Remaining length
166              -> Int              -- ^ Max node name len
167              -> Int              -- ^ Max instance name len
168              -> [[String]]       -- ^ Current command list
169              -> Bool             -- ^ Wheter to be silent
170              -> Cluster.Score    -- ^ Score at which to stop
171              -> IO (Cluster.Table, [[String]]) -- ^ The resulting table and
172                                                -- commands
173 iterateDepth ini_tbl max_rounds nmlen imlen
174              cmd_strs oneline min_score =
175     let Cluster.Table ini_nl ini_il ini_cv ini_plc = ini_tbl
176         all_inst = Container.elems ini_il
177         node_idx = map Node.idx . filter (not . Node.offline) $
178                    Container.elems ini_nl
179         fin_tbl = Cluster.checkMove node_idx ini_tbl all_inst
180         (Cluster.Table _ _ fin_cv fin_plc) = fin_tbl
181         ini_plc_len = length ini_plc
182         fin_plc_len = length fin_plc
183         allowed_next = (max_rounds < 0 || length fin_plc < max_rounds)
184     in
185       do
186         let
187             (sol_line, cmds) = Cluster.printSolutionLine ini_nl ini_il
188                                nmlen imlen (head fin_plc) fin_plc_len
189             upd_cmd_strs = cmds:cmd_strs
190         unless (oneline || fin_plc_len == ini_plc_len) $ do
191           putStrLn sol_line
192           hFlush stdout
193         (if fin_cv < ini_cv then -- this round made success, try deeper
194              if allowed_next && fin_cv > min_score
195              then iterateDepth fin_tbl max_rounds
196                   nmlen imlen upd_cmd_strs oneline min_score
197              -- don't go deeper, but return the better solution
198              else return (fin_tbl, upd_cmd_strs)
199          else
200              return (ini_tbl, cmd_strs))
201
202 -- | Formats the solution for the oneline display
203 formatOneline :: Double -> Int -> Double -> String
204 formatOneline ini_cv plc_len fin_cv =
205     printf "%.8f %d %.8f %8.3f" ini_cv plc_len fin_cv
206                (if fin_cv == 0 then 1 else ini_cv / fin_cv)
207
208 -- | Main function.
209 main :: IO ()
210 main = do
211   cmd_args <- System.getArgs
212   (opts, args) <- CLI.parseOpts cmd_args "hbal" options defaultOptions
213
214   unless (null args) $ do
215          hPutStrLn stderr "Error: this program doesn't take any arguments."
216          exitWith $ ExitFailure 1
217
218   let oneline = optOneline opts
219       verbose = optVerbose opts
220
221   (fixed_nl, il, csf) <- CLI.loadExternalData opts
222
223   let offline_names = optOffline opts
224       all_nodes = Container.elems fixed_nl
225       all_names = map Node.name all_nodes
226       offline_wrong = filter (flip notElem all_names) offline_names
227       offline_indices = map Node.idx $
228                         filter (\n -> elem (Node.name n) offline_names)
229                                all_nodes
230       m_cpu = optMcpu opts
231       m_dsk = optMdsk opts
232
233   when (length offline_wrong > 0) $ do
234          hPrintf stderr "Wrong node name(s) set as offline: %s\n"
235                      (commaJoin offline_wrong)
236          exitWith $ ExitFailure 1
237
238   let nm = Container.map (\n -> if elem (Node.idx n) offline_indices
239                                 then Node.setOffline n True
240                                 else n) fixed_nl
241       nl = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
242            nm
243
244   when (Container.size il == 0) $ do
245          (if oneline then putStrLn $ formatOneline 0 0 0
246           else printf "Cluster is empty, exiting.\n")
247          exitWith ExitSuccess
248
249   unless oneline $ printf "Loaded %d nodes, %d instances\n"
250              (Container.size nl)
251              (Container.size il)
252
253   when (length csf > 0 && not oneline && verbose > 1) $
254        printf "Note: Stripping common suffix of '%s' from names\n" csf
255
256   let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
257   unless (oneline || verbose == 0) $ printf
258              "Initial check done: %d bad nodes, %d bad instances.\n"
259              (length bad_nodes) (length bad_instances)
260
261   when (length bad_nodes > 0) $
262          putStrLn "Cluster is not N+1 happy, continuing but no guarantee \
263                   \that the cluster will end N+1 happy."
264
265   when (optShowNodes opts) $
266        do
267          putStrLn "Initial cluster status:"
268          putStrLn $ Cluster.printNodes nl
269
270   let ini_cv = Cluster.compCV nl
271       ini_tbl = Cluster.Table nl il ini_cv []
272       min_cv = optMinScore opts
273
274   when (ini_cv < min_cv) $ do
275          (if oneline then
276               putStrLn $ formatOneline ini_cv 0 ini_cv
277           else printf "Cluster is already well balanced (initial score %.6g,\n\
278                       \minimum score %.6g).\nNothing to do, exiting\n"
279                       ini_cv min_cv)
280          exitWith ExitSuccess
281
282   unless oneline (if verbose > 2 then
283                       printf "Initial coefficients: overall %.8f, %s\n"
284                       ini_cv (Cluster.printStats nl)
285                   else
286                       printf "Initial score: %.8f\n" ini_cv)
287
288   unless oneline $ putStrLn "Trying to minimize the CV..."
289   let imlen = Container.maxNameLen il
290       nmlen = Container.maxNameLen nl
291
292   (fin_tbl, cmd_strs) <- iterateDepth ini_tbl (optMaxLength opts)
293                          nmlen imlen [] oneline min_cv
294   let (Cluster.Table fin_nl _ fin_cv fin_plc) = fin_tbl
295       ord_plc = reverse fin_plc
296       sol_msg = if null fin_plc
297                 then printf "No solution found\n"
298                 else if verbose > 2
299                      then printf "Final coefficients:   overall %.8f, %s\n"
300                           fin_cv (Cluster.printStats fin_nl)
301                      else printf "Cluster score improved from %.8f to %.8f\n"
302                           ini_cv fin_cv
303                               ::String
304
305   unless oneline $ putStr sol_msg
306
307   unless (oneline || verbose == 0) $
308          printf "Solution length=%d\n" (length ord_plc)
309
310   let cmd_data = Cluster.formatCmds . reverse $ cmd_strs
311
312   when (isJust $ optShowCmds opts) $
313        do
314          let out_path = fromJust $ optShowCmds opts
315          putStrLn ""
316          (if out_path == "-" then
317               printf "Commands to run to reach the above solution:\n%s"
318                      (unlines . map ("  " ++) .
319                       filter (/= "check") .
320                       lines $ cmd_data)
321           else do
322             writeFile out_path (CLI.shTemplate ++ cmd_data)
323             printf "The commands have been written to file '%s'\n" out_path)
324
325   when (optShowNodes opts) $
326        do
327          let ini_cs = Cluster.totalResources nl
328              fin_cs = Cluster.totalResources fin_nl
329          putStrLn ""
330          putStrLn "Final cluster status:"
331          putStrLn $ Cluster.printNodes fin_nl
332          when (verbose > 3) $
333               do
334                 printf "Original: mem=%d disk=%d\n"
335                        (Cluster.cs_fmem ini_cs) (Cluster.cs_fdsk ini_cs)
336                 printf "Final:    mem=%d disk=%d\n"
337                        (Cluster.cs_fmem fin_cs) (Cluster.cs_fdsk fin_cs)
338   when oneline $
339          putStrLn $ formatOneline ini_cv (length ord_plc) fin_cv