Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ f25e5aac

History | View | Annotate | Download (25.9 kB)

1
{-| Implementation of cluster-wide logic.
2

    
3
This module holds all pure cluster-logic; I\/O related functionality
4
goes into the "Main" module for the individual binaries.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2009 Google Inc.
11

    
12
This program is free software; you can redistribute it and/or modify
13
it under the terms of the GNU General Public License as published by
14
the Free Software Foundation; either version 2 of the License, or
15
(at your option) any later version.
16

    
17
This program is distributed in the hope that it will be useful, but
18
WITHOUT ANY WARRANTY; without even the implied warranty of
19
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20
General Public License for more details.
21

    
22
You should have received a copy of the GNU General Public License
23
along with this program; if not, write to the Free Software
24
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25
02110-1301, USA.
26

    
27
-}
28

    
29
module Ganeti.HTools.Cluster
30
    (
31
     -- * Types
32
      Placement
33
    , AllocSolution
34
    , Table(..)
35
    , Score
36
    , IMove(..)
37
    , CStats(..)
38
    -- * Generic functions
39
    , totalResources
40
    -- * First phase functions
41
    , computeBadItems
42
    -- * Second phase functions
43
    , printSolution
44
    , printSolutionLine
45
    , formatCmds
46
    , printNodes
47
    -- * Balacing functions
48
    , checkMove
49
    , tryBalance
50
    , compCV
51
    , printStats
52
    -- * IAllocator functions
53
    , tryAlloc
54
    , tryReloc
55
    , collapseFailures
56
    ) where
57

    
58
import Data.List
59
import Text.Printf (printf)
60
import Data.Function
61
import Control.Monad
62

    
63
import qualified Ganeti.HTools.Container as Container
64
import qualified Ganeti.HTools.Instance as Instance
65
import qualified Ganeti.HTools.Node as Node
66
import Ganeti.HTools.Types
67
import Ganeti.HTools.Utils
68

    
69
-- * Types
70

    
71
-- | A separate name for the cluster score type.
72
type Score = Double
73

    
74
-- | The description of an instance placement.
75
type Placement = (Idx, Ndx, Ndx, Score)
76

    
77
-- | Allocation\/relocation solution.
78
type AllocSolution = ([FailMode], Int, Maybe (Score, AllocElement))
79

    
80
-- | Allocation\/relocation element.
81
type AllocElement = (Node.List, Instance.Instance, [Node.Node])
82

    
83
-- | An instance move definition
84
data IMove = Failover                -- ^ Failover the instance (f)
85
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
86
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
87
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
88
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
89
             deriving (Show)
90

    
91
-- | The complete state for the balancing solution
92
data Table = Table Node.List Instance.List Score [Placement]
93
             deriving (Show)
94

    
95
data CStats = CStats { cs_fmem :: Int    -- ^ Cluster free mem
96
                     , cs_fdsk :: Int    -- ^ Cluster free disk
97
                     , cs_amem :: Int    -- ^ Cluster allocatable mem
98
                     , cs_adsk :: Int    -- ^ Cluster allocatable disk
99
                     , cs_acpu :: Int    -- ^ Cluster allocatable cpus
100
                     , cs_mmem :: Int    -- ^ Max node allocatable mem
101
                     , cs_mdsk :: Int    -- ^ Max node allocatable disk
102
                     , cs_mcpu :: Int    -- ^ Max node allocatable cpu
103
                     , cs_imem :: Int    -- ^ Instance used mem
104
                     , cs_idsk :: Int    -- ^ Instance used disk
105
                     , cs_icpu :: Int    -- ^ Instance used cpu
106
                     , cs_tmem :: Double -- ^ Cluster total mem
107
                     , cs_tdsk :: Double -- ^ Cluster total disk
108
                     , cs_tcpu :: Double -- ^ Cluster total cpus
109
                     , cs_xmem :: Int    -- ^ Unnacounted for mem
110
                     , cs_nmem :: Int    -- ^ Node own memory
111
                     , cs_score :: Score -- ^ The cluster score
112
                     , cs_ninst :: Int   -- ^ The total number of instances
113
                     }
114

    
115
-- * Utility functions
116

    
117
-- | Verifies the N+1 status and return the affected nodes.
118
verifyN1 :: [Node.Node] -> [Node.Node]
119
verifyN1 = filter Node.failN1
120

    
121
{-| Computes the pair of bad nodes and instances.
122

    
123
The bad node list is computed via a simple 'verifyN1' check, and the
124
bad instance list is the list of primary and secondary instances of
125
those nodes.
126

    
127
-}
128
computeBadItems :: Node.List -> Instance.List ->
129
                   ([Node.Node], [Instance.Instance])
130
computeBadItems nl il =
131
  let bad_nodes = verifyN1 $ getOnline nl
132
      bad_instances = map (\idx -> Container.find idx il) .
133
                      sort . nub $
134
                      concatMap (\ n -> Node.slist n ++ Node.plist n) bad_nodes
135
  in
136
    (bad_nodes, bad_instances)
137

    
138
emptyCStats :: CStats
139
emptyCStats = CStats { cs_fmem = 0
140
                     , cs_fdsk = 0
141
                     , cs_amem = 0
142
                     , cs_adsk = 0
143
                     , cs_acpu = 0
144
                     , cs_mmem = 0
145
                     , cs_mdsk = 0
146
                     , cs_mcpu = 0
147
                     , cs_imem = 0
148
                     , cs_idsk = 0
149
                     , cs_icpu = 0
150
                     , cs_tmem = 0
151
                     , cs_tdsk = 0
152
                     , cs_tcpu = 0
153
                     , cs_xmem = 0
154
                     , cs_nmem = 0
155
                     , cs_score = 0
156
                     , cs_ninst = 0
157
                     }
158

    
159
updateCStats :: CStats -> Node.Node -> CStats
160
updateCStats cs node =
161
    let CStats { cs_fmem = x_fmem, cs_fdsk = x_fdsk,
162
                 cs_amem = x_amem, cs_acpu = x_acpu, cs_adsk = x_adsk,
163
                 cs_mmem = x_mmem, cs_mdsk = x_mdsk, cs_mcpu = x_mcpu,
164
                 cs_imem = x_imem, cs_idsk = x_idsk, cs_icpu = x_icpu,
165
                 cs_tmem = x_tmem, cs_tdsk = x_tdsk, cs_tcpu = x_tcpu,
166
                 cs_xmem = x_xmem, cs_nmem = x_nmem, cs_ninst = x_ninst
167
               }
168
            = cs
169
        inc_amem = Node.f_mem node - Node.r_mem node
170
        inc_amem' = if inc_amem > 0 then inc_amem else 0
171
        inc_adsk = Node.availDisk node
172
        inc_imem = truncate (Node.t_mem node) - Node.n_mem node
173
                   - Node.x_mem node - Node.f_mem node
174
        inc_icpu = Node.u_cpu node
175
        inc_idsk = truncate (Node.t_dsk node) - Node.f_dsk node
176

    
177
    in cs { cs_fmem = x_fmem + Node.f_mem node
178
          , cs_fdsk = x_fdsk + Node.f_dsk node
179
          , cs_amem = x_amem + inc_amem'
180
          , cs_adsk = x_adsk + inc_adsk
181
          , cs_acpu = x_acpu
182
          , cs_mmem = max x_mmem inc_amem'
183
          , cs_mdsk = max x_mdsk inc_adsk
184
          , cs_mcpu = x_mcpu
185
          , cs_imem = x_imem + inc_imem
186
          , cs_idsk = x_idsk + inc_idsk
187
          , cs_icpu = x_icpu + inc_icpu
188
          , cs_tmem = x_tmem + Node.t_mem node
189
          , cs_tdsk = x_tdsk + Node.t_dsk node
190
          , cs_tcpu = x_tcpu + Node.t_cpu node
191
          , cs_xmem = x_xmem + Node.x_mem node
192
          , cs_nmem = x_nmem + Node.n_mem node
193
          , cs_ninst = x_ninst + length (Node.plist node)
194
          }
195

    
196
-- | Compute the total free disk and memory in the cluster.
197
totalResources :: Node.List -> CStats
198
totalResources nl =
199
    let cs = foldl' updateCStats emptyCStats . Container.elems $ nl
200
    in cs { cs_score = compCV nl }
201

    
202
-- | Compute the mem and disk covariance.
203
compDetailedCV :: Node.List -> (Double, Double, Double, Double, Double, Double)
204
compDetailedCV nl =
205
    let
206
        all_nodes = Container.elems nl
207
        (offline, nodes) = partition Node.offline all_nodes
208
        mem_l = map Node.p_mem nodes
209
        dsk_l = map Node.p_dsk nodes
210
        mem_cv = varianceCoeff mem_l
211
        dsk_cv = varianceCoeff dsk_l
212
        n1_l = length $ filter Node.failN1 nodes
213
        n1_score = fromIntegral n1_l /
214
                   fromIntegral (length nodes)::Double
215
        res_l = map Node.p_rem nodes
216
        res_cv = varianceCoeff res_l
217
        offline_inst = sum . map (\n -> (length . Node.plist $ n) +
218
                                        (length . Node.slist $ n)) $ offline
219
        online_inst = sum . map (\n -> (length . Node.plist $ n) +
220
                                       (length . Node.slist $ n)) $ nodes
221
        off_score = if offline_inst == 0
222
                    then 0::Double
223
                    else fromIntegral offline_inst /
224
                         fromIntegral (offline_inst + online_inst)::Double
225
        cpu_l = map Node.p_cpu nodes
226
        cpu_cv = varianceCoeff cpu_l
227
    in (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv)
228

    
229
-- | Compute the /total/ variance.
230
compCV :: Node.List -> Double
231
compCV nl =
232
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv) =
233
            compDetailedCV nl
234
    in mem_cv + dsk_cv + n1_score + res_cv + off_score + cpu_cv
235

    
236
-- | Compute online nodes from a Node.List
237
getOnline :: Node.List -> [Node.Node]
238
getOnline = filter (not . Node.offline) . Container.elems
239

    
240
-- * hbal functions
241

    
242
-- | Compute best table. Note that the ordering of the arguments is important.
243
compareTables :: Table -> Table -> Table
244
compareTables a@(Table _ _ a_cv _) b@(Table _ _ b_cv _ ) =
245
    if a_cv > b_cv then b else a
246

    
247
-- | Applies an instance move to a given node list and instance.
248
applyMove :: Node.List -> Instance.Instance
249
          -> IMove -> OpResult (Node.List, Instance.Instance, Ndx, Ndx)
250
-- Failover (f)
251
applyMove nl inst Failover =
252
    let old_pdx = Instance.pnode inst
253
        old_sdx = Instance.snode inst
254
        old_p = Container.find old_pdx nl
255
        old_s = Container.find old_sdx nl
256
        int_p = Node.removePri old_p inst
257
        int_s = Node.removeSec old_s inst
258
        new_nl = do -- Maybe monad
259
          new_p <- Node.addPri int_s inst
260
          new_s <- Node.addSec int_p inst old_sdx
261
          let new_inst = Instance.setBoth inst old_sdx old_pdx
262
          return (Container.addTwo old_pdx new_s old_sdx new_p nl,
263
                  new_inst, old_sdx, old_pdx)
264
    in new_nl
265

    
266
-- Replace the primary (f:, r:np, f)
267
applyMove nl inst (ReplacePrimary new_pdx) =
268
    let old_pdx = Instance.pnode inst
269
        old_sdx = Instance.snode inst
270
        old_p = Container.find old_pdx nl
271
        old_s = Container.find old_sdx nl
272
        tgt_n = Container.find new_pdx nl
273
        int_p = Node.removePri old_p inst
274
        int_s = Node.removeSec old_s inst
275
        new_nl = do -- Maybe monad
276
          -- check that the current secondary can host the instance
277
          -- during the migration
278
          tmp_s <- Node.addPri int_s inst
279
          let tmp_s' = Node.removePri tmp_s inst
280
          new_p <- Node.addPri tgt_n inst
281
          new_s <- Node.addSec tmp_s' inst new_pdx
282
          let new_inst = Instance.setPri inst new_pdx
283
          return (Container.add new_pdx new_p $
284
                  Container.addTwo old_pdx int_p old_sdx new_s nl,
285
                  new_inst, new_pdx, old_sdx)
286
    in new_nl
287

    
288
-- Replace the secondary (r:ns)
289
applyMove nl inst (ReplaceSecondary new_sdx) =
290
    let old_pdx = Instance.pnode inst
291
        old_sdx = Instance.snode inst
292
        old_s = Container.find old_sdx nl
293
        tgt_n = Container.find new_sdx nl
294
        int_s = Node.removeSec old_s inst
295
        new_inst = Instance.setSec inst new_sdx
296
        new_nl = Node.addSec tgt_n inst old_pdx >>=
297
                 \new_s -> return (Container.addTwo new_sdx
298
                                   new_s old_sdx int_s nl,
299
                                   new_inst, old_pdx, new_sdx)
300
    in new_nl
301

    
302
-- Replace the secondary and failover (r:np, f)
303
applyMove nl inst (ReplaceAndFailover new_pdx) =
304
    let old_pdx = Instance.pnode inst
305
        old_sdx = Instance.snode inst
306
        old_p = Container.find old_pdx nl
307
        old_s = Container.find old_sdx nl
308
        tgt_n = Container.find new_pdx nl
309
        int_p = Node.removePri old_p inst
310
        int_s = Node.removeSec old_s inst
311
        new_nl = do -- Maybe monad
312
          new_p <- Node.addPri tgt_n inst
313
          new_s <- Node.addSec int_p inst new_pdx
314
          let new_inst = Instance.setBoth inst new_pdx old_pdx
315
          return (Container.add new_pdx new_p $
316
                  Container.addTwo old_pdx new_s old_sdx int_s nl,
317
                  new_inst, new_pdx, old_pdx)
318
    in new_nl
319

    
320
-- Failver and replace the secondary (f, r:ns)
321
applyMove nl inst (FailoverAndReplace new_sdx) =
322
    let old_pdx = Instance.pnode inst
323
        old_sdx = Instance.snode inst
324
        old_p = Container.find old_pdx nl
325
        old_s = Container.find old_sdx nl
326
        tgt_n = Container.find new_sdx nl
327
        int_p = Node.removePri old_p inst
328
        int_s = Node.removeSec old_s inst
329
        new_nl = do -- Maybe monad
330
          new_p <- Node.addPri int_s inst
331
          new_s <- Node.addSec tgt_n inst old_sdx
332
          let new_inst = Instance.setBoth inst old_sdx new_sdx
333
          return (Container.add new_sdx new_s $
334
                  Container.addTwo old_sdx new_p old_pdx int_p nl,
335
                  new_inst, old_sdx, new_sdx)
336
    in new_nl
337

    
338
-- | Tries to allocate an instance on one given node.
339
allocateOnSingle :: Node.List -> Instance.Instance -> Node.Node
340
                 -> OpResult AllocElement
341
allocateOnSingle nl inst p =
342
    let new_pdx = Node.idx p
343
        new_inst = Instance.setBoth inst new_pdx Node.noSecondary
344
        new_nl = Node.addPri p inst >>= \new_p ->
345
                 return (Container.add new_pdx new_p nl, new_inst, [new_p])
346
    in new_nl
347

    
348
-- | Tries to allocate an instance on a given pair of nodes.
349
allocateOnPair :: Node.List -> Instance.Instance -> Node.Node -> Node.Node
350
               -> OpResult AllocElement
351
allocateOnPair nl inst tgt_p tgt_s =
352
    let new_pdx = Node.idx tgt_p
353
        new_sdx = Node.idx tgt_s
354
        new_nl = do -- Maybe monad
355
          new_p <- Node.addPri tgt_p inst
356
          new_s <- Node.addSec tgt_s inst new_pdx
357
          let new_inst = Instance.setBoth inst new_pdx new_sdx
358
          return (Container.addTwo new_pdx new_p new_sdx new_s nl, new_inst,
359
                 [new_p, new_s])
360
    in new_nl
361

    
362
-- | Tries to perform an instance move and returns the best table
363
-- between the original one and the new one.
364
checkSingleStep :: Table -- ^ The original table
365
                -> Instance.Instance -- ^ The instance to move
366
                -> Table -- ^ The current best table
367
                -> IMove -- ^ The move to apply
368
                -> Table -- ^ The final best table
369
checkSingleStep ini_tbl target cur_tbl move =
370
    let
371
        Table ini_nl ini_il _ ini_plc = ini_tbl
372
        tmp_resu = applyMove ini_nl target move
373
    in
374
      case tmp_resu of
375
        OpFail _ -> cur_tbl
376
        OpGood (upd_nl, new_inst, pri_idx, sec_idx)  ->
377
            let tgt_idx = Instance.idx target
378
                upd_cvar = compCV upd_nl
379
                upd_il = Container.add tgt_idx new_inst ini_il
380
                upd_plc = (tgt_idx, pri_idx, sec_idx, upd_cvar):ini_plc
381
                upd_tbl = Table upd_nl upd_il upd_cvar upd_plc
382
            in
383
              compareTables cur_tbl upd_tbl
384

    
385
-- | Given the status of the current secondary as a valid new node and
386
-- the current candidate target node, generate the possible moves for
387
-- a instance.
388
possibleMoves :: Bool      -- ^ Whether the secondary node is a valid new node
389
              -> Ndx       -- ^ Target node candidate
390
              -> [IMove]   -- ^ List of valid result moves
391
possibleMoves True tdx =
392
    [ReplaceSecondary tdx,
393
     ReplaceAndFailover tdx,
394
     ReplacePrimary tdx,
395
     FailoverAndReplace tdx]
396

    
397
possibleMoves False tdx =
398
    [ReplaceSecondary tdx,
399
     ReplaceAndFailover tdx]
400

    
401
-- | Compute the best move for a given instance.
402
checkInstanceMove :: [Ndx]             -- ^ Allowed target node indices
403
                  -> Bool              -- ^ Whether disk moves are allowed
404
                  -> Table             -- ^ Original table
405
                  -> Instance.Instance -- ^ Instance to move
406
                  -> Table             -- ^ Best new table for this instance
407
checkInstanceMove nodes_idx disk_moves ini_tbl target =
408
    let
409
        opdx = Instance.pnode target
410
        osdx = Instance.snode target
411
        nodes = filter (\idx -> idx /= opdx && idx /= osdx) nodes_idx
412
        use_secondary = elem osdx nodes_idx
413
        aft_failover = if use_secondary -- if allowed to failover
414
                       then checkSingleStep ini_tbl target ini_tbl Failover
415
                       else ini_tbl
416
        all_moves = if disk_moves
417
                    then concatMap (possibleMoves use_secondary) nodes
418
                    else []
419
    in
420
      -- iterate over the possible nodes for this instance
421
      foldl' (checkSingleStep ini_tbl target) aft_failover all_moves
422

    
423
-- | Compute the best next move.
424
checkMove :: [Ndx]               -- ^ Allowed target node indices
425
          -> Bool                -- ^ Whether disk moves are allowed
426
          -> Table               -- ^ The current solution
427
          -> [Instance.Instance] -- ^ List of instances still to move
428
          -> Table               -- ^ The new solution
429
checkMove nodes_idx disk_moves ini_tbl victims =
430
    let Table _ _ _ ini_plc = ini_tbl
431
        -- iterate over all instances, computing the best move
432
        best_tbl =
433
            foldl'
434
            (\ step_tbl elem ->
435
                 if Instance.snode elem == Node.noSecondary then step_tbl
436
                    else compareTables step_tbl $
437
                         checkInstanceMove nodes_idx disk_moves ini_tbl elem)
438
            ini_tbl victims
439
        Table _ _ _ best_plc = best_tbl
440
    in
441
      if length best_plc == length ini_plc then -- no advancement
442
          ini_tbl
443
      else
444
          best_tbl
445

    
446
-- | Run a balance move
447

    
448
tryBalance :: Table       -- ^ The starting table
449
           -> Int         -- ^ Remaining length
450
           -> Bool        -- ^ Allow disk moves
451
           -> Score       -- ^ Score at which to stop
452
           -> Maybe Table -- ^ The resulting table and commands
453
tryBalance ini_tbl max_rounds disk_moves min_score =
454
    let Table ini_nl ini_il ini_cv ini_plc = ini_tbl
455
        ini_plc_len = length ini_plc
456
        allowed_next = (max_rounds < 0 || ini_plc_len < max_rounds) &&
457
                       ini_cv > min_score
458
    in
459
      if allowed_next
460
      then let all_inst = Container.elems ini_il
461
               node_idx = map Node.idx . filter (not . Node.offline) $
462
                          Container.elems ini_nl
463
               fin_tbl = checkMove node_idx disk_moves ini_tbl all_inst
464
               (Table _ _ fin_cv _) = fin_tbl
465
           in
466
             if fin_cv < ini_cv
467
             then Just fin_tbl -- this round made success, try deeper
468
             else Nothing
469
      else Nothing
470

    
471
-- * Allocation functions
472

    
473
-- | Build failure stats out of a list of failures
474
collapseFailures :: [FailMode] -> FailStats
475
collapseFailures flst =
476
    map (\k -> (k, length $ filter ((==) k) flst)) [minBound..maxBound]
477

    
478
-- | Update current Allocation solution and failure stats with new
479
-- elements
480
concatAllocs :: AllocSolution -> OpResult AllocElement -> AllocSolution
481
concatAllocs (flst, succ, sols) (OpFail reason) = (reason:flst, succ, sols)
482

    
483
concatAllocs (flst, succ, osols) (OpGood ns@(nl, _, _)) =
484
    let nscore = compCV nl
485
        -- Choose the old or new solution, based on the cluster score
486
        nsols = case osols of
487
                  Nothing -> Just (nscore, ns)
488
                  Just (oscore, _) ->
489
                      if oscore < nscore
490
                      then osols
491
                      else Just (nscore, ns)
492
        nsuc = succ + 1
493
    -- Note: we force evaluation of nsols here in order to keep the
494
    -- memory profile low - we know that we will need nsols for sure
495
    -- in the next cycle, so we force evaluation of nsols, since the
496
    -- foldl' in the caller will only evaluate the tuple, but not the
497
    -- elements of the tuple
498
    in nsols `seq` nsuc `seq` (flst, nsuc, nsols)
499

    
500
-- | Try to allocate an instance on the cluster.
501
tryAlloc :: (Monad m) =>
502
            Node.List         -- ^ The node list
503
         -> Instance.List     -- ^ The instance list
504
         -> Instance.Instance -- ^ The instance to allocate
505
         -> Int               -- ^ Required number of nodes
506
         -> m AllocSolution   -- ^ Possible solution list
507
tryAlloc nl _ inst 2 =
508
    let all_nodes = getOnline nl
509
        all_pairs = liftM2 (,) all_nodes all_nodes
510
        ok_pairs = filter (\(x, y) -> Node.idx x /= Node.idx y) all_pairs
511
        sols = foldl' (\cstate (p, s) ->
512
                           concatAllocs cstate $ allocateOnPair nl inst p s
513
                      ) ([], 0, Nothing) ok_pairs
514
    in return sols
515

    
516
tryAlloc nl _ inst 1 =
517
    let all_nodes = getOnline nl
518
        sols = foldl' (\cstate ->
519
                           concatAllocs cstate . allocateOnSingle nl inst
520
                      ) ([], 0, Nothing) all_nodes
521
    in return sols
522

    
523
tryAlloc _ _ _ reqn = fail $ "Unsupported number of allocation \
524
                             \destinations required (" ++ show reqn ++
525
                                               "), only two supported"
526

    
527
-- | Try to allocate an instance on the cluster.
528
tryReloc :: (Monad m) =>
529
            Node.List       -- ^ The node list
530
         -> Instance.List   -- ^ The instance list
531
         -> Idx             -- ^ The index of the instance to move
532
         -> Int             -- ^ The number of nodes required
533
         -> [Ndx]           -- ^ Nodes which should not be used
534
         -> m AllocSolution -- ^ Solution list
535
tryReloc nl il xid 1 ex_idx =
536
    let all_nodes = getOnline nl
537
        inst = Container.find xid il
538
        ex_idx' = Instance.pnode inst:ex_idx
539
        valid_nodes = filter (not . flip elem ex_idx' . Node.idx) all_nodes
540
        valid_idxes = map Node.idx valid_nodes
541
        sols1 = foldl' (\cstate x ->
542
                            let elem = do
543
                                  (mnl, i, _, _) <-
544
                                      applyMove nl inst (ReplaceSecondary x)
545
                                  return (mnl, i, [Container.find x mnl])
546
                            in concatAllocs cstate elem
547
                       ) ([], 0, Nothing) valid_idxes
548
    in return sols1
549

    
550
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
551
                                \destinations required (" ++ show reqn ++
552
                                                  "), only one supported"
553

    
554
-- * Formatting functions
555

    
556
-- | Given the original and final nodes, computes the relocation description.
557
computeMoves :: Instance.Instance -- ^ The instance to be moved
558
             -> String -- ^ The instance name
559
             -> String -- ^ Original primary
560
             -> String -- ^ Original secondary
561
             -> String -- ^ New primary
562
             -> String -- ^ New secondary
563
             -> (String, [String])
564
                -- ^ Tuple of moves and commands list; moves is containing
565
                -- either @/f/@ for failover or @/r:name/@ for replace
566
                -- secondary, while the command list holds gnt-instance
567
                -- commands (without that prefix), e.g \"@failover instance1@\"
568
computeMoves i inam a b c d
569
    -- same primary
570
    | c == a =
571
        if d == b
572
        then {- Same sec??! -} ("-", [])
573
        else {- Change of secondary -}
574
            (printf "r:%s" d, [rep d])
575
    -- failover and ...
576
    | c == b =
577
        if d == a
578
        then {- that's all -} ("f", [mig])
579
        else (printf "f r:%s" d, [mig, rep d])
580
    -- ... and keep primary as secondary
581
    | d == a =
582
        (printf "r:%s f" c, [rep c, mig])
583
    -- ... keep same secondary
584
    | d == b =
585
        (printf "f r:%s f" c, [mig, rep c, mig])
586
    -- nothing in common -
587
    | otherwise =
588
        (printf "r:%s f r:%s" c d, [rep c, mig, rep d])
589
    where morf = if Instance.running i then "migrate" else "failover"
590
          mig = printf "%s -f %s" morf inam::String
591
          rep n = printf "replace-disks -n %s %s" n inam
592

    
593
-- | Converts a placement to string format.
594
printSolutionLine :: Node.List     -- ^ The node list
595
                  -> Instance.List -- ^ The instance list
596
                  -> Int           -- ^ Maximum node name length
597
                  -> Int           -- ^ Maximum instance name length
598
                  -> Placement     -- ^ The current placement
599
                  -> Int           -- ^ The index of the placement in
600
                                   -- the solution
601
                  -> (String, [String])
602
printSolutionLine nl il nmlen imlen plc pos =
603
    let
604
        pmlen = (2*nmlen + 1)
605
        (i, p, s, c) = plc
606
        inst = Container.find i il
607
        inam = Instance.name inst
608
        npri = Container.nameOf nl p
609
        nsec = Container.nameOf nl s
610
        opri = Container.nameOf nl $ Instance.pnode inst
611
        osec = Container.nameOf nl $ Instance.snode inst
612
        (moves, cmds) =  computeMoves inst inam opri osec npri nsec
613
        ostr = printf "%s:%s" opri osec::String
614
        nstr = printf "%s:%s" npri nsec::String
615
    in
616
      (printf "  %3d. %-*s %-*s => %-*s %.8f a=%s"
617
       pos imlen inam pmlen ostr
618
       pmlen nstr c moves,
619
       cmds)
620

    
621
-- | Given a list of commands, prefix them with @gnt-instance@ and
622
-- also beautify the display a little.
623
formatCmds :: [[String]] -> String
624
formatCmds =
625
    unlines .
626
    concatMap (\(a, b) ->
627
               printf "echo step %d" (a::Int):
628
               printf "check":
629
               map ("gnt-instance " ++) b
630
              ) .
631
    zip [1..]
632

    
633
-- | Converts a solution to string format.
634
printSolution :: Node.List
635
              -> Instance.List
636
              -> [Placement]
637
              -> ([String], [[String]])
638
printSolution nl il sol =
639
    let
640
        nmlen = Container.maxNameLen nl
641
        imlen = Container.maxNameLen il
642
    in
643
      unzip $ zipWith (printSolutionLine nl il nmlen imlen) sol [1..]
644

    
645
-- | Print the node list.
646
printNodes :: Node.List -> String
647
printNodes nl =
648
    let snl = sortBy (compare `on` Node.idx) (Container.elems nl)
649
        m_name = maximum . map (length . Node.name) $ snl
650
        helper = Node.list m_name
651
        header = printf
652
                 "%2s %-*s %5s %5s %5s %5s %5s %5s %5s %5s %4s %4s \
653
                 \%3s %3s %6s %6s %5s"
654
                 " F" m_name "Name"
655
                 "t_mem" "n_mem" "i_mem" "x_mem" "f_mem" "r_mem"
656
                 "t_dsk" "f_dsk" "pcpu" "vcpu"
657
                 "pri" "sec" "p_fmem" "p_fdsk" "r_cpu"::String
658
    in unlines (header:map helper snl)
659

    
660
-- | Shows statistics for a given node list.
661
printStats :: Node.List -> String
662
printStats nl =
663
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv) =
664
            compDetailedCV nl
665
    in printf "f_mem=%.8f, r_mem=%.8f, f_dsk=%.8f, n1=%.3f, \
666
              \uf=%.3f, r_cpu=%.3f"
667
       mem_cv res_cv dsk_cv n1_score off_score cpu_cv