Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ e4d31268

History | View | Annotate | Download (28.6 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
                  , "vcpu_ratio_cv"
184
                  , "cpu_load_cv"
185
                  , "mem_load_cv"
186
                  , "disk_load_cv"
187
                  , "net_load_cv"
188
                  , "pri_tags_score"
189
                  ]
190

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

    
233
-- | Compute the /total/ variance.
234
compCV :: Node.List -> Double
235
compCV = sum . compDetailedCV
236

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

    
241
-- * hbal functions
242

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

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

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

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

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

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

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

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

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

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

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

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

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

    
447
-- | Run a balance move
448

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

    
472
-- * Allocation functions
473

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

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

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

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

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

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

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

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

    
555
-- * Formatting functions
556

    
557
-- | Given the original and final nodes, computes the relocation description.
558
computeMoves :: Instance.Instance -- ^ The instance to be moved
559
             -> String -- ^ The instance name
560
             -> IMove  -- ^ The move being performed
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 mv c d =
569
    case mv of
570
      Failover -> ("f", [mig])
571
      FailoverAndReplace _ -> (printf "f r:%s" d, [mig, rep d])
572
      ReplaceSecondary _ -> (printf "r:%s" d, [rep d])
573
      ReplaceAndFailover _ -> (printf "r:%s f" c, [rep c, mig])
574
      ReplacePrimary _ -> (printf "f r:%s f" c, [mig, rep c, mig])
575
    where morf = if Instance.running i then "migrate" else "failover"
576
          mig = printf "%s -f %s" morf inam::String
577
          rep n = printf "replace-disks -n %s %s" n inam
578

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

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

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

    
624
-- | Break a list of moves into independent groups. Note that this
625
-- will reverse the order of jobs.
626
splitJobs :: [MoveJob] -> [JobSet]
627
splitJobs = fst . foldl mergeJobs ([], [])
628

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

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

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

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

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

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

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