Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hbal.hs @ 2d6bdcc5

History | View | Annotate | Download (15 kB)

1 525bfb36 Iustin Pop
{-| Cluster rebalancer.
2 e4f08c46 Iustin Pop
3 e4f08c46 Iustin Pop
-}
4 e4f08c46 Iustin Pop
5 e2fa2baf Iustin Pop
{-
6 e2fa2baf Iustin Pop
7 72747d91 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
8 e2fa2baf Iustin Pop
9 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
10 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
11 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 e2fa2baf Iustin Pop
(at your option) any later version.
13 e2fa2baf Iustin Pop
14 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
15 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 e2fa2baf Iustin Pop
General Public License for more details.
18 e2fa2baf Iustin Pop
19 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
20 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
21 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 e2fa2baf Iustin Pop
02110-1301, USA.
23 e2fa2baf Iustin Pop
24 e2fa2baf Iustin Pop
-}
25 e2fa2baf Iustin Pop
26 e6685c53 Agata Murawska
module Ganeti.HTools.Program.Hbal
27 22278fa7 Iustin Pop
  ( main
28 22278fa7 Iustin Pop
  , options
29 22278fa7 Iustin Pop
  , arguments
30 22278fa7 Iustin Pop
  , iterateDepth
31 22278fa7 Iustin Pop
  ) where
32 e4f08c46 Iustin Pop
33 b2245847 Iustin Pop
import Control.Exception (bracket)
34 cc532bdd Iustin Pop
import Control.Monad
35 e4f08c46 Iustin Pop
import Data.List
36 646aa028 Iustin Pop
import Data.Maybe (isJust, isNothing, fromJust)
37 03cb89f0 Iustin Pop
import Data.IORef
38 7345b69b Iustin Pop
import System.Exit
39 e4f08c46 Iustin Pop
import System.IO
40 03cb89f0 Iustin Pop
import System.Posix.Process
41 03cb89f0 Iustin Pop
import System.Posix.Signals
42 e4f08c46 Iustin Pop
43 42afc235 Dato Simó
import Text.Printf (printf)
44 e4f08c46 Iustin Pop
45 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Container as Container
46 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Cluster as Cluster
47 10ef6b4e Iustin Pop
import qualified Ganeti.HTools.Group as Group
48 ec18dca9 Iustin Pop
import qualified Ganeti.HTools.Node as Node
49 b2245847 Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
50 040afc35 Iustin Pop
51 01e52493 Iustin Pop
import Ganeti.BasicTypes
52 22278fa7 Iustin Pop
import Ganeti.Common
53 0427285d Iustin Pop
import Ganeti.HTools.CLI
54 e8f89bb6 Iustin Pop
import Ganeti.HTools.ExtLoader
55 0e8ae201 Iustin Pop
import Ganeti.HTools.Types
56 4938fa30 Guido Trotter
import Ganeti.HTools.Loader
57 a81ca843 Iustin Pop
import Ganeti.OpCodes (wrapOpCode, setOpComment, setOpPriority,
58 a81ca843 Iustin Pop
                       OpCode, MetaOpCode)
59 369671f4 Dato Simó
import Ganeti.Jobs as Jobs
60 3bdbe4b3 Dato Simó
import Ganeti.Types
61 26d62e4c Iustin Pop
import Ganeti.Utils
62 e4f08c46 Iustin Pop
63 b2245847 Iustin Pop
import qualified Ganeti.Luxi as L
64 7e723913 Iustin Pop
import Ganeti.Version (version)
65 b2245847 Iustin Pop
66 179c0828 Iustin Pop
-- | Options list and functions.
67 d66aa238 Iustin Pop
options :: IO [OptType]
68 29a30533 Iustin Pop
options = do
69 29a30533 Iustin Pop
  luxi <- oLuxiSocket
70 d66aa238 Iustin Pop
  return
71 d66aa238 Iustin Pop
    [ oPrintNodes
72 d66aa238 Iustin Pop
    , oPrintInsts
73 d66aa238 Iustin Pop
    , oPrintCommands
74 d66aa238 Iustin Pop
    , oDataFile
75 d66aa238 Iustin Pop
    , oEvacMode
76 d66aa238 Iustin Pop
    , oRapiMaster
77 29a30533 Iustin Pop
    , luxi
78 d66aa238 Iustin Pop
    , oIAllocSrc
79 d66aa238 Iustin Pop
    , oExecJobs
80 d66aa238 Iustin Pop
    , oGroup
81 d66aa238 Iustin Pop
    , oMaxSolLength
82 d66aa238 Iustin Pop
    , oVerbose
83 d66aa238 Iustin Pop
    , oQuiet
84 d66aa238 Iustin Pop
    , oOfflineNode
85 d66aa238 Iustin Pop
    , oMinScore
86 d66aa238 Iustin Pop
    , oMaxCpu
87 d66aa238 Iustin Pop
    , oMinDisk
88 d66aa238 Iustin Pop
    , oMinGain
89 d66aa238 Iustin Pop
    , oMinGainLim
90 d66aa238 Iustin Pop
    , oDiskMoves
91 d66aa238 Iustin Pop
    , oSelInst
92 d66aa238 Iustin Pop
    , oInstMoves
93 d66aa238 Iustin Pop
    , oDynuFile
94 d66aa238 Iustin Pop
    , oExTags
95 d66aa238 Iustin Pop
    , oExInst
96 d66aa238 Iustin Pop
    , oSaveCluster
97 a81ca843 Iustin Pop
    , oPriority
98 d66aa238 Iustin Pop
    ]
99 e4f08c46 Iustin Pop
100 22278fa7 Iustin Pop
-- | The list of arguments supported by the program.
101 22278fa7 Iustin Pop
arguments :: [ArgCompletion]
102 22278fa7 Iustin Pop
arguments = []
103 22278fa7 Iustin Pop
104 d41f6558 Iustin Pop
-- | A simple type alias for clearer signature.
105 d41f6558 Iustin Pop
type Annotator = OpCode -> MetaOpCode
106 d41f6558 Iustin Pop
107 7e723913 Iustin Pop
-- | Wraps an 'OpCode' in a 'MetaOpCode' while also adding a comment
108 7e723913 Iustin Pop
-- about what generated the opcode.
109 d41f6558 Iustin Pop
annotateOpCode :: Annotator
110 7e723913 Iustin Pop
annotateOpCode =
111 7e723913 Iustin Pop
  setOpComment ("rebalancing via hbal " ++ version) . wrapOpCode
112 7e723913 Iustin Pop
113 6dc960bc Iustin Pop
{- | Start computing the solution at the given depth and recurse until
114 6dc960bc Iustin Pop
we find a valid solution or we exceed the maximum depth.
115 6dc960bc Iustin Pop
116 6dc960bc Iustin Pop
-}
117 e6685c53 Agata Murawska
iterateDepth :: Bool             -- ^ Whether to print moves
118 e6685c53 Agata Murawska
             -> Cluster.Table    -- ^ The starting table
119 6dc960bc Iustin Pop
             -> Int              -- ^ Remaining length
120 c0501c69 Iustin Pop
             -> Bool             -- ^ Allow disk moves
121 e7f7c003 Guido Trotter
             -> Bool             -- ^ Allow instance moves
122 6dc960bc Iustin Pop
             -> Int              -- ^ Max node name len
123 6dc960bc Iustin Pop
             -> Int              -- ^ Max instance name len
124 0e8ae201 Iustin Pop
             -> [MoveJob]        -- ^ Current command list
125 92e32d76 Iustin Pop
             -> Score            -- ^ Score at which to stop
126 848b65c9 Iustin Pop
             -> Score            -- ^ Min gain limit
127 848b65c9 Iustin Pop
             -> Score            -- ^ Min score gain
128 2e28ac32 Iustin Pop
             -> Bool             -- ^ Enable evacuation mode
129 0e8ae201 Iustin Pop
             -> IO (Cluster.Table, [MoveJob]) -- ^ The resulting table
130 0e8ae201 Iustin Pop
                                              -- and commands
131 e6685c53 Agata Murawska
iterateDepth printmove ini_tbl max_rounds disk_moves inst_moves nmlen imlen
132 e19ee6e4 Iustin Pop
             cmd_strs min_score mg_limit min_gain evac_mode =
133 2ba17362 Iustin Pop
  let Cluster.Table ini_nl ini_il _ _ = ini_tbl
134 2ba17362 Iustin Pop
      allowed_next = Cluster.doNextBalance ini_tbl max_rounds min_score
135 2ba17362 Iustin Pop
      m_fin_tbl = if allowed_next
136 e08424a8 Guido Trotter
                    then Cluster.tryBalance ini_tbl disk_moves inst_moves
137 e08424a8 Guido Trotter
                         evac_mode mg_limit min_gain
138 5ad86777 Iustin Pop
                    else Nothing
139 2ba17362 Iustin Pop
  in case m_fin_tbl of
140 2ba17362 Iustin Pop
       Just fin_tbl ->
141 2ba17362 Iustin Pop
         do
142 2ba17362 Iustin Pop
           let (Cluster.Table _ _ _ fin_plc) = fin_tbl
143 72747d91 Iustin Pop
           cur_plc@(idx, _, _, move, _) <-
144 72747d91 Iustin Pop
             exitIfEmpty "Empty placement list returned for solution?!" fin_plc
145 72747d91 Iustin Pop
           let fin_plc_len = length fin_plc
146 2ba17362 Iustin Pop
               (sol_line, cmds) = Cluster.printSolutionLine ini_nl ini_il
147 2ba17362 Iustin Pop
                                  nmlen imlen cur_plc fin_plc_len
148 2ba17362 Iustin Pop
               afn = Cluster.involvedNodes ini_il cur_plc
149 2ba17362 Iustin Pop
               upd_cmd_strs = (afn, idx, move, cmds):cmd_strs
150 e6685c53 Agata Murawska
           when printmove $ do
151 e6685c53 Agata Murawska
               putStrLn sol_line
152 e6685c53 Agata Murawska
               hFlush stdout
153 e6685c53 Agata Murawska
           iterateDepth printmove fin_tbl max_rounds disk_moves inst_moves
154 2ba17362 Iustin Pop
                        nmlen imlen upd_cmd_strs min_score
155 2ba17362 Iustin Pop
                        mg_limit min_gain evac_mode
156 2ba17362 Iustin Pop
       Nothing -> return (ini_tbl, cmd_strs)
157 6dc960bc Iustin Pop
158 5dad2589 Iustin Pop
-- | Displays the cluster stats.
159 5dad2589 Iustin Pop
printStats :: Node.List -> Node.List -> IO ()
160 5dad2589 Iustin Pop
printStats ini_nl fin_nl = do
161 5dad2589 Iustin Pop
  let ini_cs = Cluster.totalResources ini_nl
162 5dad2589 Iustin Pop
      fin_cs = Cluster.totalResources fin_nl
163 5dad2589 Iustin Pop
  printf "Original: mem=%d disk=%d\n"
164 5dad2589 Iustin Pop
             (Cluster.csFmem ini_cs) (Cluster.csFdsk ini_cs) :: IO ()
165 5dad2589 Iustin Pop
  printf "Final:    mem=%d disk=%d\n"
166 5dad2589 Iustin Pop
             (Cluster.csFmem fin_cs) (Cluster.csFdsk fin_cs)
167 5dad2589 Iustin Pop
168 5dad2589 Iustin Pop
-- | Saves the rebalance commands to a text file.
169 5dad2589 Iustin Pop
saveBalanceCommands :: Options -> String -> IO ()
170 5dad2589 Iustin Pop
saveBalanceCommands opts cmd_data = do
171 5dad2589 Iustin Pop
  let out_path = fromJust $ optShowCmds opts
172 5dad2589 Iustin Pop
  putStrLn ""
173 3603605a Iustin Pop
  if out_path == "-"
174 3603605a Iustin Pop
    then printf "Commands to run to reach the above solution:\n%s"
175 3603605a Iustin Pop
           (unlines . map ("  " ++) .
176 3603605a Iustin Pop
            filter (/= "  check") .
177 3603605a Iustin Pop
            lines $ cmd_data)
178 3603605a Iustin Pop
    else do
179 3603605a Iustin Pop
      writeFile out_path (shTemplate ++ cmd_data)
180 3603605a Iustin Pop
      printf "The commands have been written to file '%s'\n" out_path
181 5dad2589 Iustin Pop
182 3b23f238 Dato Simó
-- | Wrapper over execJobSet checking for early termination via an IORef.
183 d41f6558 Iustin Pop
execCancelWrapper :: Annotator -> String -> Node.List
184 42afc235 Dato Simó
                  -> Instance.List -> IORef Int -> [JobSet] -> IO (Result ())
185 d41f6558 Iustin Pop
execCancelWrapper _    _      _  _  _    [] = return $ Ok ()
186 d41f6558 Iustin Pop
execCancelWrapper anno master nl il cref alljss = do
187 23448f82 Iustin Pop
  cancel <- readIORef cref
188 3603605a Iustin Pop
  if cancel > 0
189 2d6bdcc5 Iustin Pop
    then do
190 2d6bdcc5 Iustin Pop
      putStrLn $ "Exiting early due to user request, " ++
191 2d6bdcc5 Iustin Pop
               show (length alljss) ++ " jobset(s) remaining."
192 2d6bdcc5 Iustin Pop
      return $ Ok ()
193 d41f6558 Iustin Pop
    else execJobSet anno master nl il cref alljss
194 23448f82 Iustin Pop
195 179c0828 Iustin Pop
-- | Execute an entire jobset.
196 d41f6558 Iustin Pop
execJobSet :: Annotator -> String -> Node.List
197 42afc235 Dato Simó
           -> Instance.List -> IORef Int -> [JobSet] -> IO (Result ())
198 d41f6558 Iustin Pop
execJobSet _    _      _  _  _    [] = return $ Ok ()
199 d41f6558 Iustin Pop
execJobSet anno master nl il cref (js:jss) = do
200 b2245847 Iustin Pop
  -- map from jobset (htools list of positions) to [[opcodes]]
201 b2245847 Iustin Pop
  let jobs = map (\(_, idx, move, _) ->
202 d41f6558 Iustin Pop
                    map anno $ Cluster.iMoveToJob nl il idx move) js
203 369671f4 Dato Simó
      descr = map (\(_, idx, _, _) -> Container.nameOf il idx) js
204 369671f4 Dato Simó
      logfn = putStrLn . ("Got job IDs" ++) . commaJoin . map (show . fromJobId)
205 b2245847 Iustin Pop
  putStrLn $ "Executing jobset for instances " ++ commaJoin descr
206 164947cc Dato Simó
  jrs <- bracket (L.getClient master) L.closeClient $
207 164947cc Dato Simó
         Jobs.execJobsWait jobs logfn
208 3603605a Iustin Pop
  case jrs of
209 42afc235 Dato Simó
    Bad x -> return $ Bad x
210 369671f4 Dato Simó
    Ok x -> if null failures
211 d41f6558 Iustin Pop
              then execCancelWrapper anno master nl il cref jss
212 42afc235 Dato Simó
              else return . Bad . unlines $ [
213 369671f4 Dato Simó
                "Not all jobs completed successfully: " ++ show failures,
214 42afc235 Dato Simó
                "Aborting."]
215 369671f4 Dato Simó
      where
216 369671f4 Dato Simó
        failures = filter ((/= JOB_STATUS_SUCCESS) . snd) x
217 b2245847 Iustin Pop
218 5dad2589 Iustin Pop
-- | Executes the jobs, if possible and desired.
219 5dad2589 Iustin Pop
maybeExecJobs :: Options
220 5dad2589 Iustin Pop
              -> [a]
221 5dad2589 Iustin Pop
              -> Node.List
222 5dad2589 Iustin Pop
              -> Instance.List
223 5dad2589 Iustin Pop
              -> [JobSet]
224 42afc235 Dato Simó
              -> IO (Result ())
225 5dad2589 Iustin Pop
maybeExecJobs opts ord_plc fin_nl il cmd_jobs =
226 2ba17362 Iustin Pop
  if optExecJobs opts && not (null ord_plc)
227 5dad2589 Iustin Pop
    then (case optLuxi opts of
228 d41f6558 Iustin Pop
            Nothing ->
229 d41f6558 Iustin Pop
              return $ Bad "Execution of commands possible only on LUXI"
230 d41f6558 Iustin Pop
            Just master ->
231 a81ca843 Iustin Pop
              let annotator = maybe id setOpPriority (optPriority opts) .
232 a81ca843 Iustin Pop
                              annotateOpCode
233 a81ca843 Iustin Pop
              in execWithCancel annotator master fin_nl il cmd_jobs)
234 42afc235 Dato Simó
    else return $ Ok ()
235 5dad2589 Iustin Pop
236 179c0828 Iustin Pop
-- | Signal handler for graceful termination.
237 9cd4288e Dato Simó
handleSigInt :: IORef Int -> IO ()
238 9cd4288e Dato Simó
handleSigInt cref = do
239 543e859d Iustin Pop
  writeIORef cref 1
240 543e859d Iustin Pop
  putStrLn ("Cancel request registered, will exit at" ++
241 543e859d Iustin Pop
            " the end of the current job set...")
242 543e859d Iustin Pop
243 179c0828 Iustin Pop
-- | Signal handler for immediate termination.
244 9cd4288e Dato Simó
handleSigTerm :: IORef Int -> IO ()
245 9cd4288e Dato Simó
handleSigTerm cref = do
246 543e859d Iustin Pop
  -- update the cref to 2, just for consistency
247 543e859d Iustin Pop
  writeIORef cref 2
248 543e859d Iustin Pop
  putStrLn "Double cancel request, exiting now..."
249 543e859d Iustin Pop
  exitImmediately $ ExitFailure 2
250 03cb89f0 Iustin Pop
251 3b23f238 Dato Simó
-- | Prepares to run a set of jobsets with handling of signals and early
252 3b23f238 Dato Simó
-- termination.
253 d41f6558 Iustin Pop
execWithCancel :: Annotator -> String -> Node.List -> Instance.List -> [JobSet]
254 42afc235 Dato Simó
               -> IO (Result ())
255 d41f6558 Iustin Pop
execWithCancel anno master fin_nl il cmd_jobs = do
256 03cb89f0 Iustin Pop
  cref <- newIORef 0
257 543e859d Iustin Pop
  mapM_ (\(hnd, sig) -> installHandler sig (Catch (hnd cref)) Nothing)
258 9cd4288e Dato Simó
    [(handleSigTerm, softwareTermination), (handleSigInt, keyboardSignal)]
259 d41f6558 Iustin Pop
  execCancelWrapper anno master fin_nl il cref cmd_jobs
260 03cb89f0 Iustin Pop
261 5dad2589 Iustin Pop
-- | Select the target node group.
262 5dad2589 Iustin Pop
selectGroup :: Options -> Group.List -> Node.List -> Instance.List
263 5dad2589 Iustin Pop
            -> IO (String, (Node.List, Instance.List))
264 5dad2589 Iustin Pop
selectGroup opts gl nlf ilf = do
265 646aa028 Iustin Pop
  let ngroups = Cluster.splitCluster nlf ilf
266 646aa028 Iustin Pop
  when (length ngroups > 1 && isNothing (optGroup opts)) $ do
267 646aa028 Iustin Pop
    hPutStrLn stderr "Found multiple node groups:"
268 e0c85e08 Iustin Pop
    mapM_ (hPutStrLn stderr . ("  " ++) . Group.name .
269 d5072e4c Iustin Pop
           flip Container.find gl . fst) ngroups
270 707cd3d7 Helga Velroyen
    exitErr "Aborting."
271 646aa028 Iustin Pop
272 5dad2589 Iustin Pop
  case optGroup opts of
273 10ef6b4e Iustin Pop
    Nothing -> do
274 72747d91 Iustin Pop
      (gidx, cdata) <- exitIfEmpty "No groups found by splitCluster?!" ngroups
275 72747d91 Iustin Pop
      let grp = Container.find gidx gl
276 2ba17362 Iustin Pop
      return (Group.name grp, cdata)
277 10ef6b4e Iustin Pop
    Just g -> case Container.findByName gl g of
278 646aa028 Iustin Pop
      Nothing -> do
279 646aa028 Iustin Pop
        hPutStrLn stderr $ "Node group " ++ g ++
280 646aa028 Iustin Pop
          " not found. Node group list is:"
281 10ef6b4e Iustin Pop
        mapM_ (hPutStrLn stderr . ("  " ++) . Group.name ) (Container.elems gl)
282 707cd3d7 Helga Velroyen
        exitErr "Aborting."
283 10ef6b4e Iustin Pop
      Just grp ->
284 10ef6b4e Iustin Pop
          case lookup (Group.idx grp) ngroups of
285 3603605a Iustin Pop
            Nothing ->
286 2072221f Iustin Pop
              -- This will only happen if there are no nodes assigned
287 2072221f Iustin Pop
              -- to this group
288 2072221f Iustin Pop
              return (Group.name grp, (Container.empty, Container.empty))
289 10ef6b4e Iustin Pop
            Just cdata -> return (Group.name grp, cdata)
290 646aa028 Iustin Pop
291 5dad2589 Iustin Pop
-- | Do a few checks on the cluster data.
292 e19ee6e4 Iustin Pop
checkCluster :: Int -> Node.List -> Instance.List -> IO ()
293 e19ee6e4 Iustin Pop
checkCluster verbose nl il = do
294 5dad2589 Iustin Pop
  -- nothing to do on an empty cluster
295 5dad2589 Iustin Pop
  when (Container.null il) $ do
296 e19ee6e4 Iustin Pop
         printf "Cluster is empty, exiting.\n"::IO ()
297 2cdaf225 Iustin Pop
         exitSuccess
298 5dad2589 Iustin Pop
299 5dad2589 Iustin Pop
  -- hbal doesn't currently handle split clusters
300 5dad2589 Iustin Pop
  let split_insts = Cluster.findSplitInstances nl il
301 a7e1fd89 Iustin Pop
  unless (null split_insts || verbose <= 1) $ do
302 5dad2589 Iustin Pop
    hPutStrLn stderr "Found instances belonging to multiple node groups:"
303 5dad2589 Iustin Pop
    mapM_ (\i -> hPutStrLn stderr $ "  " ++ Instance.name i) split_insts
304 a7e1fd89 Iustin Pop
    hPutStrLn stderr "These instances will not be moved."
305 5dad2589 Iustin Pop
306 e19ee6e4 Iustin Pop
  printf "Loaded %d nodes, %d instances\n"
307 5dad2589 Iustin Pop
             (Container.size nl)
308 e19ee6e4 Iustin Pop
             (Container.size il)::IO ()
309 5dad2589 Iustin Pop
310 5dad2589 Iustin Pop
  let csf = commonSuffix nl il
311 e19ee6e4 Iustin Pop
  when (not (null csf) && verbose > 1) $
312 5dad2589 Iustin Pop
       printf "Note: Stripping common suffix of '%s' from names\n" csf
313 5dad2589 Iustin Pop
314 5dad2589 Iustin Pop
-- | Do a few checks on the selected group data.
315 e19ee6e4 Iustin Pop
checkGroup :: Int -> String -> Node.List -> Instance.List -> IO ()
316 e19ee6e4 Iustin Pop
checkGroup verbose gname nl il = do
317 e19ee6e4 Iustin Pop
  printf "Group size %d nodes, %d instances\n"
318 e4f08c46 Iustin Pop
             (Container.size nl)
319 e19ee6e4 Iustin Pop
             (Container.size il)::IO ()
320 a0529a64 Iustin Pop
321 10ef6b4e Iustin Pop
  putStrLn $ "Selected node group: " ++ gname
322 646aa028 Iustin Pop
323 e4f08c46 Iustin Pop
  let (bad_nodes, bad_instances) = Cluster.computeBadItems nl il
324 bfa99f7a Iustin Pop
  unless (verbose < 1) $ printf
325 27f96567 Iustin Pop
             "Initial check done: %d bad nodes, %d bad instances.\n"
326 e4f08c46 Iustin Pop
             (length bad_nodes) (length bad_instances)
327 e4f08c46 Iustin Pop
328 2cdaf225 Iustin Pop
  unless (null bad_nodes) $
329 289c3835 Iustin Pop
         putStrLn "Cluster is not N+1 happy, continuing but no guarantee \
330 289c3835 Iustin Pop
                  \that the cluster will end N+1 happy."
331 e4f08c46 Iustin Pop
332 5dad2589 Iustin Pop
-- | Check that we actually need to rebalance.
333 5dad2589 Iustin Pop
checkNeedRebalance :: Options -> Score -> IO ()
334 5dad2589 Iustin Pop
checkNeedRebalance opts ini_cv = do
335 5dad2589 Iustin Pop
  let min_cv = optMinScore opts
336 5dad2589 Iustin Pop
  when (ini_cv < min_cv) $ do
337 e19ee6e4 Iustin Pop
         printf "Cluster is already well balanced (initial score %.6g,\n\
338 e19ee6e4 Iustin Pop
                \minimum score %.6g).\nNothing to do, exiting\n"
339 e19ee6e4 Iustin Pop
                ini_cv min_cv:: IO ()
340 2cdaf225 Iustin Pop
         exitSuccess
341 5dad2589 Iustin Pop
342 5dad2589 Iustin Pop
-- | Main function.
343 21839f47 Iustin Pop
main :: Options -> [String] -> IO ()
344 21839f47 Iustin Pop
main opts args = do
345 707cd3d7 Helga Velroyen
  unless (null args) $ exitErr "This program doesn't take any arguments."
346 5dad2589 Iustin Pop
347 e19ee6e4 Iustin Pop
  let verbose = optVerbose opts
348 5dad2589 Iustin Pop
      shownodes = optShowNodes opts
349 5dad2589 Iustin Pop
      showinsts = optShowInsts opts
350 5dad2589 Iustin Pop
351 e77bc89b Iustin Pop
  ini_cdata@(ClusterData gl fixed_nl ilf ctags ipol) <- loadExternalData opts
352 5dad2589 Iustin Pop
353 e77bc89b Iustin Pop
  when (verbose > 1) $ do
354 5dad2589 Iustin Pop
       putStrLn $ "Loaded cluster tags: " ++ intercalate "," ctags
355 e77bc89b Iustin Pop
       putStrLn $ "Loaded cluster ipolicy: " ++ show ipol
356 5dad2589 Iustin Pop
357 5296ee23 Iustin Pop
  nlf <- setNodeStatus opts fixed_nl
358 e19ee6e4 Iustin Pop
  checkCluster verbose nlf ilf
359 5dad2589 Iustin Pop
360 5dad2589 Iustin Pop
  maybeSaveData (optSaveCluster opts) "original" "before balancing" ini_cdata
361 5dad2589 Iustin Pop
362 5dad2589 Iustin Pop
  (gname, (nl, il)) <- selectGroup opts gl nlf ilf
363 5dad2589 Iustin Pop
364 e19ee6e4 Iustin Pop
  checkGroup verbose gname nl il
365 5dad2589 Iustin Pop
366 33e44f0c Iustin Pop
  maybePrintInsts showinsts "Initial" (Cluster.printInsts nl il)
367 507fda3f Iustin Pop
368 417f6b50 Iustin Pop
  maybePrintNodes shownodes "Initial cluster" (Cluster.printNodes nl)
369 e4f08c46 Iustin Pop
370 e4f08c46 Iustin Pop
  let ini_cv = Cluster.compCV nl
371 e4f08c46 Iustin Pop
      ini_tbl = Cluster.Table nl il ini_cv []
372 b0517d61 Iustin Pop
      min_cv = optMinScore opts
373 b0517d61 Iustin Pop
374 5dad2589 Iustin Pop
  checkNeedRebalance opts ini_cv
375 b0517d61 Iustin Pop
376 3603605a Iustin Pop
  if verbose > 2
377 2922d2c5 René Nussbaumer
    then printf "Initial coefficients: overall %.8f\n%s"
378 2922d2c5 René Nussbaumer
           ini_cv (Cluster.printStats "  " nl)::IO ()
379 3603605a Iustin Pop
    else printf "Initial score: %.8f\n" ini_cv
380 e4f08c46 Iustin Pop
381 e19ee6e4 Iustin Pop
  putStrLn "Trying to minimize the CV..."
382 14c972c7 Iustin Pop
  let imlen = maximum . map (length . Instance.alias) $ Container.elems il
383 14c972c7 Iustin Pop
      nmlen = maximum . map (length . Node.alias) $ Container.elems nl
384 7dfaafb1 Iustin Pop
385 e6685c53 Agata Murawska
  (fin_tbl, cmd_strs) <- iterateDepth True ini_tbl (optMaxLength opts)
386 c0501c69 Iustin Pop
                         (optDiskMoves opts)
387 e7f7c003 Guido Trotter
                         (optInstMoves opts)
388 e19ee6e4 Iustin Pop
                         nmlen imlen [] min_cv
389 848b65c9 Iustin Pop
                         (optMinGainLim opts) (optMinGain opts)
390 848b65c9 Iustin Pop
                         (optEvacMode opts)
391 507fda3f Iustin Pop
  let (Cluster.Table fin_nl fin_il fin_cv fin_plc) = fin_tbl
392 e4f08c46 Iustin Pop
      ord_plc = reverse fin_plc
393 cc532bdd Iustin Pop
      sol_msg = case () of
394 cc532bdd Iustin Pop
                  _ | null fin_plc -> printf "No solution found\n"
395 cc532bdd Iustin Pop
                    | verbose > 2 ->
396 2922d2c5 René Nussbaumer
                        printf "Final coefficients:   overall %.8f\n%s"
397 2922d2c5 René Nussbaumer
                        fin_cv (Cluster.printStats "  " fin_nl)
398 cc532bdd Iustin Pop
                    | otherwise ->
399 cc532bdd Iustin Pop
                        printf "Cluster score improved from %.8f to %.8f\n"
400 cc532bdd Iustin Pop
                        ini_cv fin_cv ::String
401 e4f08c46 Iustin Pop
402 e19ee6e4 Iustin Pop
  putStr sol_msg
403 7eff5b09 Iustin Pop
404 bfa99f7a Iustin Pop
  unless (verbose < 1) $
405 7eff5b09 Iustin Pop
         printf "Solution length=%d\n" (length ord_plc)
406 e4f08c46 Iustin Pop
407 b2245847 Iustin Pop
  let cmd_jobs = Cluster.splitJobs cmd_strs
408 e0eb63f0 Iustin Pop
409 2cdaf225 Iustin Pop
  when (isJust $ optShowCmds opts) .
410 5dad2589 Iustin Pop
       saveBalanceCommands opts $ Cluster.formatCmds cmd_jobs
411 e0eb63f0 Iustin Pop
412 4188449c Iustin Pop
  maybeSaveData (optSaveCluster opts) "balanced" "after balancing"
413 71375ef7 Iustin Pop
                ini_cdata { cdNodes = fin_nl, cdInstances = fin_il }
414 b2245847 Iustin Pop
415 33e44f0c Iustin Pop
  maybePrintInsts showinsts "Final" (Cluster.printInsts fin_nl fin_il)
416 507fda3f Iustin Pop
417 417f6b50 Iustin Pop
  maybePrintNodes shownodes "Final cluster" (Cluster.printNodes fin_nl)
418 417f6b50 Iustin Pop
419 5dad2589 Iustin Pop
  when (verbose > 3) $ printStats nl fin_nl
420 5dad2589 Iustin Pop
421 42afc235 Dato Simó
  exitIfBad "hbal" =<< maybeExecJobs opts ord_plc fin_nl il cmd_jobs