Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hbal.hs @ 7ec2f76b

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