Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Program / Hbal.hs @ 29a30533

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