Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Program / Hbal.hs @ 01606931

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