Fix/enhance makefile rules after the rename
[ganeti-local] / hbal.hs
1 {-| Solver for N+1 cluster errors
2
3 -}
4
5 module Main (main) where
6
7 import Data.List
8 import Data.Function
9 import Monad
10 import System
11 import System.IO
12 import System.Console.GetOpt
13 import qualified System
14
15 import Text.Printf (printf)
16
17 import qualified Ganeti.HTools.Container as Container
18 import qualified Ganeti.HTools.Cluster as Cluster
19 import qualified Ganeti.HTools.Version as Version
20 import Ganeti.HTools.Rapi
21 import Ganeti.HTools.Utils
22
23 -- | Command line options structure.
24 data Options = Options
25     { optShowNodes :: Bool     -- ^ Whether to show node status
26     , optShowCmds  :: Bool     -- ^ Whether to show the command list
27     , optOneline   :: Bool     -- ^ Switch output to a single line
28     , optNodef     :: FilePath -- ^ Path to the nodes file
29     , optInstf     :: FilePath -- ^ Path to the instances file
30     , optMaxLength :: Int      -- ^ Stop after this many steps
31     , optMaster    :: String   -- ^ Collect data from RAPI
32     , optVerbose   :: Int      -- ^ Verbosity level
33     , optShowVer   :: Bool     -- ^ Just show the program version
34     } deriving Show
35
36 -- | Default values for the command line options.
37 defaultOptions :: Options
38 defaultOptions  = Options
39  { optShowNodes = False
40  , optShowCmds  = False
41  , optOneline   = False
42  , optNodef     = "nodes"
43  , optInstf     = "instances"
44  , optMaxLength = -1
45  , optMaster    = ""
46  , optVerbose   = 0
47  , optShowVer   = False
48  }
49
50 -- | Options list and functions
51 options :: [OptDescr (Options -> Options)]
52 options =
53     [ Option ['p']     ["print-nodes"]
54       (NoArg (\ opts -> opts { optShowNodes = True }))
55       "print the final node list"
56     , Option ['C']     ["print-commands"]
57       (NoArg (\ opts -> opts { optShowCmds = True }))
58       "print the ganeti command list for reaching the solution"
59     , Option ['o']     ["oneline"]
60       (NoArg (\ opts -> opts { optOneline = True }))
61       "print the ganeti command list for reaching the solution"
62     , Option ['n']     ["nodes"]
63       (ReqArg (\ f opts -> opts { optNodef = f }) "FILE")
64       "the node list FILE"
65     , Option ['i']     ["instances"]
66       (ReqArg (\ f opts -> opts { optInstf =  f }) "FILE")
67       "the instance list FILE"
68     , Option ['m']     ["master"]
69       (ReqArg (\ m opts -> opts { optMaster = m }) "ADDRESS")
70       "collect data via RAPI at the given ADDRESS"
71     , Option ['l']     ["max-length"]
72       (ReqArg (\ i opts -> opts { optMaxLength =  (read i)::Int }) "N")
73       "cap the solution at this many moves (useful for very unbalanced \
74       \clusters)"
75     , Option ['v']     ["verbose"]
76       (NoArg (\ opts -> let nv = (optVerbose opts)
77                         in opts { optVerbose = nv + 1 }))
78       "increase the verbosity level"
79     , Option ['V']     ["version"]
80       (NoArg (\ opts -> opts { optShowVer = True}))
81       "show the version of the program"
82     ]
83
84 -- | Command line parser, using the 'options' structure.
85 parseOpts :: [String] -> IO (Options, [String])
86 parseOpts argv =
87     case getOpt Permute options argv of
88       (o,n,[]  ) ->
89           return (foldl (flip id) defaultOptions o, n)
90       (_,_,errs) ->
91           ioError (userError (concat errs ++ usageInfo header options))
92       where header = printf "hbal %s\nUsage: hbal [OPTION...]"
93                      Version.version
94
95 {- | Start computing the solution at the given depth and recurse until
96 we find a valid solution or we exceed the maximum depth.
97
98 -}
99 iterateDepth :: Cluster.Table    -- ^ The starting table
100              -> Int              -- ^ Remaining length
101              -> [(Int, String)]  -- ^ Node idx to name list
102              -> [(Int, String)]  -- ^ Inst idx to name list
103              -> Int              -- ^ Max node name len
104              -> Int              -- ^ Max instance name len
105              -> [[String]]       -- ^ Current command list
106              -> Bool             -- ^ Wheter to be silent
107              -> IO (Cluster.Table, [[String]]) -- ^ The resulting table and
108                                                -- commands
109 iterateDepth ini_tbl max_rounds ktn kti nmlen imlen cmd_strs oneline =
110     let Cluster.Table ini_nl ini_il ini_cv ini_plc = ini_tbl
111         all_inst = Container.elems ini_il
112         node_idx = Container.keys ini_nl
113         fin_tbl = Cluster.checkMove node_idx ini_tbl all_inst
114         (Cluster.Table _ _ fin_cv fin_plc) = fin_tbl
115         ini_plc_len = length ini_plc
116         fin_plc_len = length fin_plc
117         allowed_next = (max_rounds < 0 || length fin_plc < max_rounds)
118     in
119       do
120         let
121             (sol_line, cmds) = Cluster.printSolutionLine ini_il ktn kti
122                                nmlen imlen (head fin_plc) fin_plc_len
123             upd_cmd_strs = cmds:cmd_strs
124         unless (oneline || fin_plc_len == ini_plc_len) $ do
125           putStrLn sol_line
126           hFlush stdout
127         (if fin_cv < ini_cv then -- this round made success, try deeper
128              if allowed_next
129              then iterateDepth fin_tbl max_rounds ktn kti
130                   nmlen imlen upd_cmd_strs oneline
131              -- don't go deeper, but return the better solution
132              else return (fin_tbl, upd_cmd_strs)
133          else
134              return (ini_tbl, cmd_strs))
135
136 -- | Main function.
137 main :: IO ()
138 main = do
139   cmd_args <- System.getArgs
140   (opts, _) <- parseOpts cmd_args
141
142   when (optShowVer opts) $ do
143          putStr $ showVersion "hbal"
144          exitWith ExitSuccess
145
146   let oneline = optOneline opts
147       verbose = optVerbose opts
148       (node_data, inst_data) =
149           case optMaster opts of
150             "" -> (readFile $ optNodef opts,
151                    readFile $ optInstf opts)
152             host -> (readData getNodes host,
153                      readData getInstances host)
154
155   (nl, il, csf, ktn, kti) <- liftM2 Cluster.loadData node_data inst_data
156
157   unless oneline $ printf "Loaded %d nodes, %d instances\n"
158              (Container.size nl)
159              (Container.size il)
160
161   when (length csf > 0 && not oneline && verbose > 0) $ do
162          printf "Note: Stripping common suffix of '%s' from names\n" csf
163
164   let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
165   unless (oneline || verbose == 0) $ printf
166              "Initial check done: %d bad nodes, %d bad instances.\n"
167              (length bad_nodes) (length bad_instances)
168
169   when (length bad_nodes > 0) $ do
170          putStrLn "Cluster is not N+1 happy, continuing but no guarantee \
171                   \that the cluster will end N+1 happy."
172
173   when (optShowNodes opts) $
174        do
175          putStrLn "Initial cluster status:"
176          putStrLn $ Cluster.printNodes ktn nl
177
178   let ini_cv = Cluster.compCV nl
179       ini_tbl = Cluster.Table nl il ini_cv []
180   unless oneline (if verbose > 1 then
181                       printf "Initial coefficients: overall %.8f, %s\n"
182                       ini_cv (Cluster.printStats nl)
183                   else
184                       printf "Initial score: %.8f\n" ini_cv)
185
186   unless oneline $ putStrLn "Trying to minimize the CV..."
187   let mlen_fn = maximum . (map length) . snd . unzip
188       imlen = mlen_fn kti
189       nmlen = mlen_fn ktn
190
191   (fin_tbl, cmd_strs) <- iterateDepth ini_tbl (optMaxLength opts)
192                          ktn kti nmlen imlen [] oneline
193   let (Cluster.Table fin_nl _ fin_cv fin_plc) = fin_tbl
194       ord_plc = reverse fin_plc
195       sol_msg = if null fin_plc
196                 then printf "No solution found\n"
197                 else (if verbose > 1
198                       then printf "Final coefficients:   overall %.8f, %s\n"
199                            fin_cv (Cluster.printStats fin_nl)
200                       else printf "Cluster score improved from %.8f to %.8f\n"
201                            ini_cv fin_cv
202                      )
203
204   unless oneline $ putStr sol_msg
205
206   unless (oneline || verbose == 0) $
207          printf "Solution length=%d\n" (length ord_plc)
208
209   when (optShowCmds opts) $
210        do
211          putStrLn ""
212          putStrLn "Commands to run to reach the above solution:"
213          putStr . Cluster.formatCmds . reverse $ cmd_strs
214   when (optShowNodes opts) $
215        do
216          let (orig_mem, orig_disk) = Cluster.totalResources nl
217              (final_mem, final_disk) = Cluster.totalResources fin_nl
218          putStrLn ""
219          putStrLn "Final cluster status:"
220          putStrLn $ Cluster.printNodes ktn fin_nl
221          when (verbose > 2) $
222               do
223                 printf "Original: mem=%d disk=%d\n" orig_mem orig_disk
224                 printf "Final:    mem=%d disk=%d\n" final_mem final_disk
225   when oneline $ do
226          printf "%.8f %d %.8f %8.3f\n"
227                 ini_cv (length ord_plc) fin_cv (ini_cv / fin_cv)