Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 6b20875c

History | View | Annotate | Download (28.2 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
    , involvedNodes
48
    , splitJobs
49
    -- * Balacing functions
50
    , checkMove
51
    , tryBalance
52
    , compCV
53
    , printStats
54
    , iMoveToJob
55
    -- * IAllocator functions
56
    , tryAlloc
57
    , tryReloc
58
    , collapseFailures
59
    ) where
60

    
61
import Data.List
62
import Text.Printf (printf)
63
import Data.Function
64
import Control.Monad
65

    
66
import qualified Ganeti.HTools.Container as Container
67
import qualified Ganeti.HTools.Instance as Instance
68
import qualified Ganeti.HTools.Node as Node
69
import Ganeti.HTools.Types
70
import Ganeti.HTools.Utils
71
import qualified Ganeti.OpCodes as OpCodes
72

    
73
-- * Types
74

    
75
-- | A separate name for the cluster score type.
76
type Score = Double
77

    
78
-- | The description of an instance placement.
79
type Placement = ( Idx   -- ^ The index of the instance being moved
80
                 , Ndx   -- ^ New primary node
81
                 , Ndx   -- ^ New secondary node
82
                 , IMove -- ^ The move being performed
83
                 , Score -- ^ The score of the cluster after this move
84
                 )
85

    
86
-- | Allocation\/relocation solution.
87
type AllocSolution = ([FailMode], Int, Maybe (Score, AllocElement))
88

    
89
-- | Allocation\/relocation element.
90
type AllocElement = (Node.List, Instance.Instance, [Node.Node])
91

    
92
-- | An instance move definition
93
data IMove = Failover                -- ^ Failover the instance (f)
94
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
95
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
96
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
97
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
98
             deriving (Show)
99

    
100
-- | The complete state for the balancing solution
101
data Table = Table Node.List Instance.List Score [Placement]
102
             deriving (Show)
103

    
104
data CStats = CStats { cs_fmem :: Int    -- ^ Cluster free mem
105
                     , cs_fdsk :: Int    -- ^ Cluster free disk
106
                     , cs_amem :: Int    -- ^ Cluster allocatable mem
107
                     , cs_adsk :: Int    -- ^ Cluster allocatable disk
108
                     , cs_acpu :: Int    -- ^ Cluster allocatable cpus
109
                     , cs_mmem :: Int    -- ^ Max node allocatable mem
110
                     , cs_mdsk :: Int    -- ^ Max node allocatable disk
111
                     , cs_mcpu :: Int    -- ^ Max node allocatable cpu
112
                     , cs_imem :: Int    -- ^ Instance used mem
113
                     , cs_idsk :: Int    -- ^ Instance used disk
114
                     , cs_icpu :: Int    -- ^ Instance used cpu
115
                     , cs_tmem :: Double -- ^ Cluster total mem
116
                     , cs_tdsk :: Double -- ^ Cluster total disk
117
                     , cs_tcpu :: Double -- ^ Cluster total cpus
118
                     , cs_xmem :: Int    -- ^ Unnacounted for mem
119
                     , cs_nmem :: Int    -- ^ Node own memory
120
                     , cs_score :: Score -- ^ The cluster score
121
                     , cs_ninst :: Int   -- ^ The total number of instances
122
                     }
123

    
124
-- * Utility functions
125

    
126
-- | Verifies the N+1 status and return the affected nodes.
127
verifyN1 :: [Node.Node] -> [Node.Node]
128
verifyN1 = filter Node.failN1
129

    
130
{-| Computes the pair of bad nodes and instances.
131

    
132
The bad node list is computed via a simple 'verifyN1' check, and the
133
bad instance list is the list of primary and secondary instances of
134
those nodes.
135

    
136
-}
137
computeBadItems :: Node.List -> Instance.List ->
138
                   ([Node.Node], [Instance.Instance])
139
computeBadItems nl il =
140
  let bad_nodes = verifyN1 $ getOnline nl
141
      bad_instances = map (\idx -> Container.find idx il) .
142
                      sort . nub $
143
                      concatMap (\ n -> Node.slist n ++ Node.plist n) bad_nodes
144
  in
145
    (bad_nodes, bad_instances)
146

    
147
emptyCStats :: CStats
148
emptyCStats = CStats { cs_fmem = 0
149
                     , cs_fdsk = 0
150
                     , cs_amem = 0
151
                     , cs_adsk = 0
152
                     , cs_acpu = 0
153
                     , cs_mmem = 0
154
                     , cs_mdsk = 0
155
                     , cs_mcpu = 0
156
                     , cs_imem = 0
157
                     , cs_idsk = 0
158
                     , cs_icpu = 0
159
                     , cs_tmem = 0
160
                     , cs_tdsk = 0
161
                     , cs_tcpu = 0
162
                     , cs_xmem = 0
163
                     , cs_nmem = 0
164
                     , cs_score = 0
165
                     , cs_ninst = 0
166
                     }
167

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

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

    
205
-- | Compute the total free disk and memory in the cluster.
206
totalResources :: Node.List -> CStats
207
totalResources nl =
208
    let cs = foldl' updateCStats emptyCStats . Container.elems $ nl
209
    in cs { cs_score = compCV nl }
210

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

    
238
-- | Compute the /total/ variance.
239
compCV :: Node.List -> Double
240
compCV nl =
241
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv) =
242
            compDetailedCV nl
243
    in mem_cv + dsk_cv + n1_score + res_cv + off_score + cpu_cv
244

    
245
-- | Compute online nodes from a Node.List
246
getOnline :: Node.List -> [Node.Node]
247
getOnline = filter (not . Node.offline) . Container.elems
248

    
249
-- * hbal functions
250

    
251
-- | Compute best table. Note that the ordering of the arguments is important.
252
compareTables :: Table -> Table -> Table
253
compareTables a@(Table _ _ a_cv _) b@(Table _ _ b_cv _ ) =
254
    if a_cv > b_cv then b else a
255

    
256
-- | Applies an instance move to a given node list and instance.
257
applyMove :: Node.List -> Instance.Instance
258
          -> IMove -> OpResult (Node.List, Instance.Instance, Ndx, Ndx)
259
-- Failover (f)
260
applyMove nl inst Failover =
261
    let old_pdx = Instance.pnode inst
262
        old_sdx = Instance.snode inst
263
        old_p = Container.find old_pdx nl
264
        old_s = Container.find old_sdx nl
265
        int_p = Node.removePri old_p inst
266
        int_s = Node.removeSec old_s inst
267
        new_nl = do -- Maybe monad
268
          new_p <- Node.addPri int_s inst
269
          new_s <- Node.addSec int_p inst old_sdx
270
          let new_inst = Instance.setBoth inst old_sdx old_pdx
271
          return (Container.addTwo old_pdx new_s old_sdx new_p nl,
272
                  new_inst, old_sdx, old_pdx)
273
    in new_nl
274

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

    
297
-- Replace the secondary (r:ns)
298
applyMove nl inst (ReplaceSecondary new_sdx) =
299
    let old_pdx = Instance.pnode inst
300
        old_sdx = Instance.snode inst
301
        old_s = Container.find old_sdx nl
302
        tgt_n = Container.find new_sdx nl
303
        int_s = Node.removeSec old_s inst
304
        new_inst = Instance.setSec inst new_sdx
305
        new_nl = Node.addSec tgt_n inst old_pdx >>=
306
                 \new_s -> return (Container.addTwo new_sdx
307
                                   new_s old_sdx int_s nl,
308
                                   new_inst, old_pdx, new_sdx)
309
    in new_nl
310

    
311
-- Replace the secondary and failover (r:np, f)
312
applyMove nl inst (ReplaceAndFailover new_pdx) =
313
    let old_pdx = Instance.pnode inst
314
        old_sdx = Instance.snode inst
315
        old_p = Container.find old_pdx nl
316
        old_s = Container.find old_sdx nl
317
        tgt_n = Container.find new_pdx nl
318
        int_p = Node.removePri old_p inst
319
        int_s = Node.removeSec old_s inst
320
        new_nl = do -- Maybe monad
321
          new_p <- Node.addPri tgt_n inst
322
          new_s <- Node.addSec int_p inst new_pdx
323
          let new_inst = Instance.setBoth inst new_pdx old_pdx
324
          return (Container.add new_pdx new_p $
325
                  Container.addTwo old_pdx new_s old_sdx int_s nl,
326
                  new_inst, new_pdx, old_pdx)
327
    in new_nl
328

    
329
-- Failver and replace the secondary (f, r:ns)
330
applyMove nl inst (FailoverAndReplace new_sdx) =
331
    let old_pdx = Instance.pnode inst
332
        old_sdx = Instance.snode inst
333
        old_p = Container.find old_pdx nl
334
        old_s = Container.find old_sdx nl
335
        tgt_n = Container.find new_sdx nl
336
        int_p = Node.removePri old_p inst
337
        int_s = Node.removeSec old_s inst
338
        new_nl = do -- Maybe monad
339
          new_p <- Node.addPri int_s inst
340
          new_s <- Node.addSec tgt_n inst old_sdx
341
          let new_inst = Instance.setBoth inst old_sdx new_sdx
342
          return (Container.add new_sdx new_s $
343
                  Container.addTwo old_sdx new_p old_pdx int_p nl,
344
                  new_inst, old_sdx, new_sdx)
345
    in new_nl
346

    
347
-- | Tries to allocate an instance on one given node.
348
allocateOnSingle :: Node.List -> Instance.Instance -> Node.Node
349
                 -> OpResult AllocElement
350
allocateOnSingle nl inst p =
351
    let new_pdx = Node.idx p
352
        new_inst = Instance.setBoth inst new_pdx Node.noSecondary
353
        new_nl = Node.addPri p inst >>= \new_p ->
354
                 return (Container.add new_pdx new_p nl, new_inst, [new_p])
355
    in new_nl
356

    
357
-- | Tries to allocate an instance on a given pair of nodes.
358
allocateOnPair :: Node.List -> Instance.Instance -> Node.Node -> Node.Node
359
               -> OpResult AllocElement
360
allocateOnPair nl inst tgt_p tgt_s =
361
    let new_pdx = Node.idx tgt_p
362
        new_sdx = Node.idx tgt_s
363
        new_nl = do -- Maybe monad
364
          new_p <- Node.addPri tgt_p inst
365
          new_s <- Node.addSec tgt_s inst new_pdx
366
          let new_inst = Instance.setBoth inst new_pdx new_sdx
367
          return (Container.addTwo new_pdx new_p new_sdx new_s nl, new_inst,
368
                 [new_p, new_s])
369
    in new_nl
370

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

    
394
-- | Given the status of the current secondary as a valid new node and
395
-- the current candidate target node, generate the possible moves for
396
-- a instance.
397
possibleMoves :: Bool      -- ^ Whether the secondary node is a valid new node
398
              -> Ndx       -- ^ Target node candidate
399
              -> [IMove]   -- ^ List of valid result moves
400
possibleMoves True tdx =
401
    [ReplaceSecondary tdx,
402
     ReplaceAndFailover tdx,
403
     ReplacePrimary tdx,
404
     FailoverAndReplace tdx]
405

    
406
possibleMoves False tdx =
407
    [ReplaceSecondary tdx,
408
     ReplaceAndFailover tdx]
409

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

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

    
455
-- | Run a balance move
456

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

    
480
-- * Allocation functions
481

    
482
-- | Build failure stats out of a list of failures
483
collapseFailures :: [FailMode] -> FailStats
484
collapseFailures flst =
485
    map (\k -> (k, length $ filter ((==) k) flst)) [minBound..maxBound]
486

    
487
-- | Update current Allocation solution and failure stats with new
488
-- elements
489
concatAllocs :: AllocSolution -> OpResult AllocElement -> AllocSolution
490
concatAllocs (flst, cntok, sols) (OpFail reason) = (reason:flst, cntok, sols)
491

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

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

    
525
tryAlloc nl _ inst 1 =
526
    let all_nodes = getOnline nl
527
        sols = foldl' (\cstate ->
528
                           concatAllocs cstate . allocateOnSingle nl inst
529
                      ) ([], 0, Nothing) all_nodes
530
    in return sols
531

    
532
tryAlloc _ _ _ reqn = fail $ "Unsupported number of allocation \
533
                             \destinations required (" ++ show reqn ++
534
                                               "), only two supported"
535

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

    
559
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
560
                                \destinations required (" ++ show reqn ++
561
                                                  "), only one supported"
562

    
563
-- * Formatting functions
564

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

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

    
630
-- | Return the instance and involved nodes in an instance move.
631
involvedNodes :: Instance.List -> Placement -> [Ndx]
632
involvedNodes il plc =
633
    let (i, np, ns, _, _) = plc
634
        inst = Container.find i il
635
        op = Instance.pnode inst
636
        os = Instance.snode inst
637
    in nub [np, ns, op, os]
638

    
639
-- | Inner function for splitJobs, that either appends the next job to
640
-- the current jobset, or starts a new jobset.
641
mergeJobs :: ([JobSet], [Ndx]) -> MoveJob -> ([JobSet], [Ndx])
642
mergeJobs ([], _) n@(ndx, _) = ([[n]], ndx)
643
mergeJobs (cjs@(j:js), nbuf) n@(ndx, _)
644
    | null (ndx `intersect` nbuf) = ((n:j):js, ndx ++ nbuf)
645
    | otherwise = ([n]:cjs, ndx)
646

    
647
-- | Break a list of moves into independent groups. Note that this
648
-- will reverse the order of jobs.
649
splitJobs :: [MoveJob] -> [JobSet]
650
splitJobs = fst . foldl mergeJobs ([], [])
651

    
652
-- | Given a list of commands, prefix them with @gnt-instance@ and
653
-- also beautify the display a little.
654
formatJob :: Int -> Int -> (Int, MoveJob) -> [String]
655
formatJob jsn jsl (sn, (_, cmds)) =
656
    let out =
657
            printf "  echo job %d/%d" jsn sn:
658
            printf "  check":
659
            map ("  gnt-instance " ++) cmds
660
    in if sn == 1
661
       then ["", printf "echo jobset %d, %d jobs" jsn jsl] ++ out
662
       else out
663

    
664
-- | Given a list of commands, prefix them with @gnt-instance@ and
665
-- also beautify the display a little.
666
formatCmds :: [JobSet] -> String
667
formatCmds =
668
    unlines .
669
    concatMap (\(jsn, js) -> concatMap (formatJob jsn (length js))
670
                             (zip [1..] js)) .
671
    zip [1..]
672

    
673
-- | Converts a solution to string format.
674
printSolution :: Node.List
675
              -> Instance.List
676
              -> [Placement]
677
              -> ([String], [[String]])
678
printSolution nl il sol =
679
    let
680
        nmlen = Container.maxNameLen nl
681
        imlen = Container.maxNameLen il
682
    in
683
      unzip $ zipWith (printSolutionLine nl il nmlen imlen) sol [1..]
684

    
685
-- | Print the node list.
686
printNodes :: Node.List -> String
687
printNodes nl =
688
    let snl = sortBy (compare `on` Node.idx) (Container.elems nl)
689
        m_name = maximum . map (length . Node.name) $ snl
690
        helper = Node.list m_name
691
        header = printf
692
                 "%2s %-*s %5s %5s %5s %5s %5s %5s %5s %5s %4s %4s \
693
                 \%3s %3s %6s %6s %5s"
694
                 " F" m_name "Name"
695
                 "t_mem" "n_mem" "i_mem" "x_mem" "f_mem" "r_mem"
696
                 "t_dsk" "f_dsk" "pcpu" "vcpu"
697
                 "pri" "sec" "p_fmem" "p_fdsk" "r_cpu"::String
698
    in unlines (header:map helper snl)
699

    
700
-- | Shows statistics for a given node list.
701
printStats :: Node.List -> String
702
printStats nl =
703
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv) =
704
            compDetailedCV nl
705
    in printf "f_mem=%.8f, r_mem=%.8f, f_dsk=%.8f, n1=%.3f, \
706
              \uf=%.3f, r_cpu=%.3f"
707
       mem_cv res_cv dsk_cv n1_score off_score cpu_cv
708

    
709
-- | Convert a placement into a list of OpCodes (basically a job).
710
iMoveToJob :: String -> Node.List -> Instance.List
711
          -> Idx -> IMove -> [OpCodes.OpCode]
712
iMoveToJob csf nl il idx move =
713
    let iname = Container.nameOf il idx ++ csf
714
        lookNode n = Just (Container.nameOf nl n ++ csf)
715
        opF = OpCodes.OpFailoverInstance iname False
716
        opR n = OpCodes.OpReplaceDisks iname (lookNode n)
717
                OpCodes.ReplaceNewSecondary [] Nothing
718
    in case move of
719
         Failover -> [ opF ]
720
         ReplacePrimary np -> [ opF, opR np, opF ]
721
         ReplaceSecondary ns -> [ opR ns ]
722
         ReplaceAndFailover np -> [ opR np, opF ]
723
         FailoverAndReplace ns -> [ opF, opR ns ]