Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 673f0f00

History | View | Annotate | Download (28.8 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
      AllocSolution
33
    , Table(..)
34
    , CStats(..)
35
    -- * Generic functions
36
    , totalResources
37
    -- * First phase functions
38
    , computeBadItems
39
    -- * Second phase functions
40
    , printSolution
41
    , printSolutionLine
42
    , formatCmds
43
    , involvedNodes
44
    , splitJobs
45
    -- * Display functions
46
    , printNodes
47
    , printInsts
48
    -- * Balacing functions
49
    , checkMove
50
    , tryBalance
51
    , compCV
52
    , printStats
53
    , iMoveToJob
54
    -- * IAllocator functions
55
    , tryAlloc
56
    , tryReloc
57
    , collapseFailures
58
    ) where
59

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

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

    
72
-- * Types
73

    
74
-- | Allocation\/relocation solution.
75
type AllocSolution = ([FailMode], Int, Maybe (Score, AllocElement))
76

    
77
-- | Allocation\/relocation element.
78
type AllocElement = (Node.List, Instance.Instance, [Node.Node])
79

    
80

    
81
-- | The complete state for the balancing solution
82
data Table = Table Node.List Instance.List Score [Placement]
83
             deriving (Show)
84

    
85
data CStats = CStats { csFmem :: Int    -- ^ Cluster free mem
86
                     , csFdsk :: Int    -- ^ Cluster free disk
87
                     , csAmem :: Int    -- ^ Cluster allocatable mem
88
                     , csAdsk :: Int    -- ^ Cluster allocatable disk
89
                     , csAcpu :: Int    -- ^ Cluster allocatable cpus
90
                     , csMmem :: Int    -- ^ Max node allocatable mem
91
                     , csMdsk :: Int    -- ^ Max node allocatable disk
92
                     , csMcpu :: Int    -- ^ Max node allocatable cpu
93
                     , csImem :: Int    -- ^ Instance used mem
94
                     , csIdsk :: Int    -- ^ Instance used disk
95
                     , csIcpu :: Int    -- ^ Instance used cpu
96
                     , csTmem :: Double -- ^ Cluster total mem
97
                     , csTdsk :: Double -- ^ Cluster total disk
98
                     , csTcpu :: Double -- ^ Cluster total cpus
99
                     , csXmem :: Int    -- ^ Unnacounted for mem
100
                     , csNmem :: Int    -- ^ Node own memory
101
                     , csScore :: Score -- ^ The cluster score
102
                     , csNinst :: Int   -- ^ The total number of instances
103
                     }
104

    
105
-- * Utility functions
106

    
107
-- | Verifies the N+1 status and return the affected nodes.
108
verifyN1 :: [Node.Node] -> [Node.Node]
109
verifyN1 = filter Node.failN1
110

    
111
{-| Computes the pair of bad nodes and instances.
112

    
113
The bad node list is computed via a simple 'verifyN1' check, and the
114
bad instance list is the list of primary and secondary instances of
115
those nodes.
116

    
117
-}
118
computeBadItems :: Node.List -> Instance.List ->
119
                   ([Node.Node], [Instance.Instance])
120
computeBadItems nl il =
121
  let bad_nodes = verifyN1 $ getOnline nl
122
      bad_instances = map (\idx -> Container.find idx il) .
123
                      sort . nub $
124
                      concatMap (\ n -> Node.sList n ++ Node.pList n) bad_nodes
125
  in
126
    (bad_nodes, bad_instances)
127

    
128
-- | Zero-initializer for the CStats type
129
emptyCStats :: CStats
130
emptyCStats = CStats 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
131

    
132
-- | Update stats with data from a new node
133
updateCStats :: CStats -> Node.Node -> CStats
134
updateCStats cs node =
135
    let CStats { csFmem = x_fmem, csFdsk = x_fdsk,
136
                 csAmem = x_amem, csAcpu = x_acpu, csAdsk = x_adsk,
137
                 csMmem = x_mmem, csMdsk = x_mdsk, csMcpu = x_mcpu,
138
                 csImem = x_imem, csIdsk = x_idsk, csIcpu = x_icpu,
139
                 csTmem = x_tmem, csTdsk = x_tdsk, csTcpu = x_tcpu,
140
                 csXmem = x_xmem, csNmem = x_nmem, csNinst = x_ninst
141
               }
142
            = cs
143
        inc_amem = Node.fMem node - Node.rMem node
144
        inc_amem' = if inc_amem > 0 then inc_amem else 0
145
        inc_adsk = Node.availDisk node
146
        inc_imem = truncate (Node.tMem node) - Node.nMem node
147
                   - Node.xMem node - Node.fMem node
148
        inc_icpu = Node.uCpu node
149
        inc_idsk = truncate (Node.tDsk node) - Node.fDsk node
150

    
151
    in cs { csFmem = x_fmem + Node.fMem node
152
          , csFdsk = x_fdsk + Node.fDsk node
153
          , csAmem = x_amem + inc_amem'
154
          , csAdsk = x_adsk + inc_adsk
155
          , csAcpu = x_acpu
156
          , csMmem = max x_mmem inc_amem'
157
          , csMdsk = max x_mdsk inc_adsk
158
          , csMcpu = x_mcpu
159
          , csImem = x_imem + inc_imem
160
          , csIdsk = x_idsk + inc_idsk
161
          , csIcpu = x_icpu + inc_icpu
162
          , csTmem = x_tmem + Node.tMem node
163
          , csTdsk = x_tdsk + Node.tDsk node
164
          , csTcpu = x_tcpu + Node.tCpu node
165
          , csXmem = x_xmem + Node.xMem node
166
          , csNmem = x_nmem + Node.nMem node
167
          , csNinst = x_ninst + length (Node.pList node)
168
          }
169

    
170
-- | Compute the total free disk and memory in the cluster.
171
totalResources :: Node.List -> CStats
172
totalResources nl =
173
    let cs = foldl' updateCStats emptyCStats . Container.elems $ nl
174
    in cs { csScore = compCV nl }
175

    
176
-- | The names of the individual elements in the CV list
177
detailedCVNames :: [String]
178
detailedCVNames = [ "free_mem_cv"
179
                  , "free_disk_cv"
180
                  , "n1_score"
181
                  , "reserved_mem_cv"
182
                  , "offline_all_cnt"
183
                  , "offline_pri_cnt"
184
                  , "vcpu_ratio_cv"
185
                  , "cpu_load_cv"
186
                  , "mem_load_cv"
187
                  , "disk_load_cv"
188
                  , "net_load_cv"
189
                  , "pri_tags_score"
190
                  ]
191

    
192
-- | Compute the mem and disk covariance.
193
compDetailedCV :: Node.List -> [Double]
194
compDetailedCV nl =
195
    let
196
        all_nodes = Container.elems nl
197
        (offline, nodes) = partition Node.offline all_nodes
198
        mem_l = map Node.pMem nodes
199
        dsk_l = map Node.pDsk nodes
200
        -- metric: memory covariance
201
        mem_cv = varianceCoeff mem_l
202
        -- metric: disk covariance
203
        dsk_cv = varianceCoeff dsk_l
204
        n1_l = length $ filter Node.failN1 nodes
205
        -- metric: ratio of failN1 nodes
206
        n1_score = fromIntegral n1_l /
207
                   fromIntegral (length nodes)::Double
208
        res_l = map Node.pRem nodes
209
        -- metric: reserved memory covariance
210
        res_cv = varianceCoeff res_l
211
        -- offline instances metrics
212
        offline_ipri = sum . map (length . Node.pList) $ offline
213
        offline_isec = sum . map (length . Node.sList) $ offline
214
        -- metric: count of instances on offline nodes
215
        off_score = fromIntegral (offline_ipri + offline_isec)::Double
216
        -- metric: count of primary instances on offline nodes (this
217
        -- helps with evacuation/failover of primary instances on
218
        -- 2-node clusters with one node offline)
219
        off_pri_score = fromIntegral offline_ipri::Double
220
        cpu_l = map Node.pCpu nodes
221
        -- metric: covariance of vcpu/pcpu ratio
222
        cpu_cv = varianceCoeff cpu_l
223
        -- metrics: covariance of cpu, memory, disk and network load
224
        (c_load, m_load, d_load, n_load) = unzip4 $
225
            map (\n ->
226
                     let DynUtil c1 m1 d1 n1 = Node.utilLoad n
227
                         DynUtil c2 m2 d2 n2 = Node.utilPool n
228
                     in (c1/c2, m1/m2, d1/d2, n1/n2)
229
                ) nodes
230
        -- metric: conflicting instance count
231
        pri_tags_inst = sum $ map Node.conflictingPrimaries nodes
232
        pri_tags_score = fromIntegral pri_tags_inst::Double
233
    in [ mem_cv, dsk_cv, n1_score, res_cv, off_score, off_pri_score, cpu_cv
234
       , varianceCoeff c_load, varianceCoeff m_load
235
       , varianceCoeff d_load, varianceCoeff n_load
236
       , pri_tags_score ]
237

    
238
-- | Compute the /total/ variance.
239
compCV :: Node.List -> Double
240
compCV = sum . compDetailedCV
241

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

    
246
-- * hbal functions
247

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

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

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

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

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

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

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

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

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

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

    
403
possibleMoves False tdx =
404
    [ReplaceSecondary tdx,
405
     ReplaceAndFailover tdx]
406

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

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

    
452
-- | Run a balance move
453

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

    
477
-- * Allocation functions
478

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

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

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

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

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

    
529
tryAlloc _ _ _ reqn = fail $ "Unsupported number of allocation \
530
                             \destinations required (" ++ show reqn ++
531
                                               "), only two supported"
532

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

    
556
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
557
                                \destinations required (" ++ show reqn ++
558
                                                  "), only one supported"
559

    
560
-- * Formatting functions
561

    
562
-- | Given the original and final nodes, computes the relocation description.
563
computeMoves :: Instance.Instance -- ^ The instance to be moved
564
             -> String -- ^ The instance name
565
             -> IMove  -- ^ The move being performed
566
             -> String -- ^ New primary
567
             -> String -- ^ New secondary
568
             -> (String, [String])
569
                -- ^ Tuple of moves and commands list; moves is containing
570
                -- either @/f/@ for failover or @/r:name/@ for replace
571
                -- secondary, while the command list holds gnt-instance
572
                -- commands (without that prefix), e.g \"@failover instance1@\"
573
computeMoves i inam mv c d =
574
    case mv of
575
      Failover -> ("f", [mig])
576
      FailoverAndReplace _ -> (printf "f r:%s" d, [mig, rep d])
577
      ReplaceSecondary _ -> (printf "r:%s" d, [rep d])
578
      ReplaceAndFailover _ -> (printf "r:%s f" c, [rep c, mig])
579
      ReplacePrimary _ -> (printf "f r:%s f" c, [mig, rep c, mig])
580
    where morf = if Instance.running i then "migrate" else "failover"
581
          mig = printf "%s -f %s" morf inam::String
582
          rep n = printf "replace-disks -n %s %s" n inam
583

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

    
612
-- | Return the instance and involved nodes in an instance move.
613
involvedNodes :: Instance.List -> Placement -> [Ndx]
614
involvedNodes il plc =
615
    let (i, np, ns, _, _) = plc
616
        inst = Container.find i il
617
        op = Instance.pNode inst
618
        os = Instance.sNode inst
619
    in nub [np, ns, op, os]
620

    
621
-- | Inner function for splitJobs, that either appends the next job to
622
-- the current jobset, or starts a new jobset.
623
mergeJobs :: ([JobSet], [Ndx]) -> MoveJob -> ([JobSet], [Ndx])
624
mergeJobs ([], _) n@(ndx, _, _, _) = ([[n]], ndx)
625
mergeJobs (cjs@(j:js), nbuf) n@(ndx, _, _, _)
626
    | null (ndx `intersect` nbuf) = ((n:j):js, ndx ++ nbuf)
627
    | otherwise = ([n]:cjs, ndx)
628

    
629
-- | Break a list of moves into independent groups. Note that this
630
-- will reverse the order of jobs.
631
splitJobs :: [MoveJob] -> [JobSet]
632
splitJobs = fst . foldl mergeJobs ([], [])
633

    
634
-- | Given a list of commands, prefix them with @gnt-instance@ and
635
-- also beautify the display a little.
636
formatJob :: Int -> Int -> (Int, MoveJob) -> [String]
637
formatJob jsn jsl (sn, (_, _, _, cmds)) =
638
    let out =
639
            printf "  echo job %d/%d" jsn sn:
640
            printf "  check":
641
            map ("  gnt-instance " ++) cmds
642
    in if sn == 1
643
       then ["", printf "echo jobset %d, %d jobs" jsn jsl] ++ out
644
       else out
645

    
646
-- | Given a list of commands, prefix them with @gnt-instance@ and
647
-- also beautify the display a little.
648
formatCmds :: [JobSet] -> String
649
formatCmds =
650
    unlines .
651
    concatMap (\(jsn, js) -> concatMap (formatJob jsn (length js))
652
                             (zip [1..] js)) .
653
    zip [1..]
654

    
655
-- | Converts a solution to string format.
656
printSolution :: Node.List
657
              -> Instance.List
658
              -> [Placement]
659
              -> ([String], [[String]])
660
printSolution nl il sol =
661
    let
662
        nmlen = Container.maxNameLen nl
663
        imlen = Container.maxNameLen il
664
    in
665
      unzip $ zipWith (printSolutionLine nl il nmlen imlen) sol [1..]
666

    
667
-- | Print the node list.
668
printNodes :: Node.List -> [String] -> String
669
printNodes nl fs =
670
    let fields = if null fs
671
                 then Node.defaultFields
672
                 else fs
673
        snl = sortBy (compare `on` Node.idx) (Container.elems nl)
674
        (header, isnum) = unzip $ map Node.showHeader fields
675
    in unlines . map ((:) ' ' .  intercalate " ") $
676
       formatTable (header:map (Node.list fields) snl) isnum
677

    
678
-- | Print the instance list.
679
printInsts :: Node.List -> Instance.List -> String
680
printInsts nl il =
681
    let sil = sortBy (compare `on` Instance.idx) (Container.elems il)
682
        helper inst = [ if Instance.running inst then "R" else " "
683
                      , Instance.name inst
684
                      , Container.nameOf nl (Instance.pNode inst)
685
                      , (let sdx = Instance.sNode inst
686
                         in if sdx == Node.noSecondary
687
                            then  ""
688
                            else Container.nameOf nl sdx)
689
                      , printf "%3d" $ Instance.vcpus inst
690
                      , printf "%5d" $ Instance.mem inst
691
                      , printf "%5d" $ Instance.dsk inst `div` 1024
692
                      , printf "%5.3f" lC
693
                      , printf "%5.3f" lM
694
                      , printf "%5.3f" lD
695
                      , printf "%5.3f" lN
696
                      ]
697
            where DynUtil lC lM lD lN = Instance.util inst
698
        header = [ "F", "Name", "Pri_node", "Sec_node", "vcpu", "mem"
699
                 , "dsk", "lCpu", "lMem", "lDsk", "lNet" ]
700
        isnum = False:False:False:False:repeat True
701
    in unlines . map ((:) ' ' . intercalate " ") $
702
       formatTable (header:map helper sil) isnum
703

    
704
-- | Shows statistics for a given node list.
705
printStats :: Node.List -> String
706
printStats nl =
707
    let dcvs = compDetailedCV nl
708
        hd = zip (detailedCVNames ++ repeat "unknown") dcvs
709
        formatted = map (\(header, val) ->
710
                             printf "%s=%.8f" header val::String) hd
711
    in intercalate ", " formatted
712

    
713
-- | Convert a placement into a list of OpCodes (basically a job).
714
iMoveToJob :: String -> Node.List -> Instance.List
715
          -> Idx -> IMove -> [OpCodes.OpCode]
716
iMoveToJob csf nl il idx move =
717
    let inst = Container.find idx il
718
        iname = Instance.name inst ++ csf
719
        lookNode n = Just (Container.nameOf nl n ++ csf)
720
        opF = if Instance.running inst
721
              then OpCodes.OpMigrateInstance iname True False
722
              else OpCodes.OpFailoverInstance iname False
723
        opR n = OpCodes.OpReplaceDisks iname (lookNode n)
724
                OpCodes.ReplaceNewSecondary [] Nothing
725
    in case move of
726
         Failover -> [ opF ]
727
         ReplacePrimary np -> [ opF, opR np, opF ]
728
         ReplaceSecondary ns -> [ opR ns ]
729
         ReplaceAndFailover np -> [ opR np, opF ]
730
         FailoverAndReplace ns -> [ opF, opR ns ]