Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 2060348b

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

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

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

    
71
-- * Types
72

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

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

    
79

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

    
84
data CStats = CStats { cs_fmem :: Int    -- ^ Cluster free mem
85
                     , cs_fdsk :: Int    -- ^ Cluster free disk
86
                     , cs_amem :: Int    -- ^ Cluster allocatable mem
87
                     , cs_adsk :: Int    -- ^ Cluster allocatable disk
88
                     , cs_acpu :: Int    -- ^ Cluster allocatable cpus
89
                     , cs_mmem :: Int    -- ^ Max node allocatable mem
90
                     , cs_mdsk :: Int    -- ^ Max node allocatable disk
91
                     , cs_mcpu :: Int    -- ^ Max node allocatable cpu
92
                     , cs_imem :: Int    -- ^ Instance used mem
93
                     , cs_idsk :: Int    -- ^ Instance used disk
94
                     , cs_icpu :: Int    -- ^ Instance used cpu
95
                     , cs_tmem :: Double -- ^ Cluster total mem
96
                     , cs_tdsk :: Double -- ^ Cluster total disk
97
                     , cs_tcpu :: Double -- ^ Cluster total cpus
98
                     , cs_xmem :: Int    -- ^ Unnacounted for mem
99
                     , cs_nmem :: Int    -- ^ Node own memory
100
                     , cs_score :: Score -- ^ The cluster score
101
                     , cs_ninst :: Int   -- ^ The total number of instances
102
                     }
103

    
104
-- * Utility functions
105

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

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

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

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

    
127
emptyCStats :: CStats
128
emptyCStats = CStats { cs_fmem = 0
129
                     , cs_fdsk = 0
130
                     , cs_amem = 0
131
                     , cs_adsk = 0
132
                     , cs_acpu = 0
133
                     , cs_mmem = 0
134
                     , cs_mdsk = 0
135
                     , cs_mcpu = 0
136
                     , cs_imem = 0
137
                     , cs_idsk = 0
138
                     , cs_icpu = 0
139
                     , cs_tmem = 0
140
                     , cs_tdsk = 0
141
                     , cs_tcpu = 0
142
                     , cs_xmem = 0
143
                     , cs_nmem = 0
144
                     , cs_score = 0
145
                     , cs_ninst = 0
146
                     }
147

    
148
updateCStats :: CStats -> Node.Node -> CStats
149
updateCStats cs node =
150
    let CStats { cs_fmem = x_fmem, cs_fdsk = x_fdsk,
151
                 cs_amem = x_amem, cs_acpu = x_acpu, cs_adsk = x_adsk,
152
                 cs_mmem = x_mmem, cs_mdsk = x_mdsk, cs_mcpu = x_mcpu,
153
                 cs_imem = x_imem, cs_idsk = x_idsk, cs_icpu = x_icpu,
154
                 cs_tmem = x_tmem, cs_tdsk = x_tdsk, cs_tcpu = x_tcpu,
155
                 cs_xmem = x_xmem, cs_nmem = x_nmem, cs_ninst = x_ninst
156
               }
157
            = cs
158
        inc_amem = Node.fMem node - Node.rMem node
159
        inc_amem' = if inc_amem > 0 then inc_amem else 0
160
        inc_adsk = Node.availDisk node
161
        inc_imem = truncate (Node.tMem node) - Node.nMem node
162
                   - Node.xMem node - Node.fMem node
163
        inc_icpu = Node.uCpu node
164
        inc_idsk = truncate (Node.tDsk node) - Node.fDsk node
165

    
166
    in cs { cs_fmem = x_fmem + Node.fMem node
167
          , cs_fdsk = x_fdsk + Node.fDsk node
168
          , cs_amem = x_amem + inc_amem'
169
          , cs_adsk = x_adsk + inc_adsk
170
          , cs_acpu = x_acpu
171
          , cs_mmem = max x_mmem inc_amem'
172
          , cs_mdsk = max x_mdsk inc_adsk
173
          , cs_mcpu = x_mcpu
174
          , cs_imem = x_imem + inc_imem
175
          , cs_idsk = x_idsk + inc_idsk
176
          , cs_icpu = x_icpu + inc_icpu
177
          , cs_tmem = x_tmem + Node.tMem node
178
          , cs_tdsk = x_tdsk + Node.tDsk node
179
          , cs_tcpu = x_tcpu + Node.tCpu node
180
          , cs_xmem = x_xmem + Node.xMem node
181
          , cs_nmem = x_nmem + Node.nMem node
182
          , cs_ninst = x_ninst + length (Node.pList node)
183
          }
184

    
185
-- | Compute the total free disk and memory in the cluster.
186
totalResources :: Node.List -> CStats
187
totalResources nl =
188
    let cs = foldl' updateCStats emptyCStats . Container.elems $ nl
189
    in cs { cs_score = compCV nl }
190

    
191
-- | The names of the individual elements in the CV list
192
detailedCVNames :: [String]
193
detailedCVNames = [ "free_mem_cv"
194
                  , "free_disk_cv"
195
                  , "n1_score"
196
                  , "reserved_mem_cv"
197
                  , "offline_score"
198
                  , "vcpu_ratio_cv"
199
                  ]
200

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

    
228
-- | Compute the /total/ variance.
229
compCV :: Node.List -> Double
230
compCV = sum . compDetailedCV
231

    
232
-- | Compute online nodes from a Node.List
233
getOnline :: Node.List -> [Node.Node]
234
getOnline = filter (not . Node.offline) . Container.elems
235

    
236
-- * hbal functions
237

    
238
-- | Compute best table. Note that the ordering of the arguments is important.
239
compareTables :: Table -> Table -> Table
240
compareTables a@(Table _ _ a_cv _) b@(Table _ _ b_cv _ ) =
241
    if a_cv > b_cv then b else a
242

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

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

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

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

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

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

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

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

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

    
393
possibleMoves False tdx =
394
    [ReplaceSecondary tdx,
395
     ReplaceAndFailover tdx]
396

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

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

    
442
-- | Run a balance move
443

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

    
467
-- * Allocation functions
468

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

    
474
-- | Update current Allocation solution and failure stats with new
475
-- elements
476
concatAllocs :: AllocSolution -> OpResult AllocElement -> AllocSolution
477
concatAllocs (flst, cntok, sols) (OpFail reason) = (reason:flst, cntok, sols)
478

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

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

    
512
tryAlloc nl _ inst 1 =
513
    let all_nodes = getOnline nl
514
        sols = foldl' (\cstate ->
515
                           concatAllocs cstate . allocateOnSingle nl inst
516
                      ) ([], 0, Nothing) all_nodes
517
    in return sols
518

    
519
tryAlloc _ _ _ reqn = fail $ "Unsupported number of allocation \
520
                             \destinations required (" ++ show reqn ++
521
                                               "), only two supported"
522

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

    
546
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
547
                                \destinations required (" ++ show reqn ++
548
                                                  "), only one supported"
549

    
550
-- * Formatting functions
551

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

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

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

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

    
634
-- | Break a list of moves into independent groups. Note that this
635
-- will reverse the order of jobs.
636
splitJobs :: [MoveJob] -> [JobSet]
637
splitJobs = fst . foldl mergeJobs ([], [])
638

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

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

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

    
672
-- | Print the node list.
673
printNodes :: Node.List -> String
674
printNodes nl =
675
    let snl = sortBy (compare `on` Node.idx) (Container.elems nl)
676
        m_name = maximum . map (length . Node.name) $ snl
677
        helper = Node.list m_name
678
        header = printf
679
                 "%2s %-*s %5s %5s %5s %5s %5s %5s %5s %5s %4s %4s \
680
                 \%3s %3s %6s %6s %5s"
681
                 " F" m_name "Name"
682
                 "t_mem" "n_mem" "i_mem" "x_mem" "f_mem" "r_mem"
683
                 "t_dsk" "f_dsk" "pcpu" "vcpu"
684
                 "pri" "sec" "p_fmem" "p_fdsk" "r_cpu"::String
685
    in unlines (header:map helper snl)
686

    
687
-- | Shows statistics for a given node list.
688
printStats :: Node.List -> String
689
printStats nl =
690
    let dcvs = compDetailedCV nl
691
        hd = zip (detailedCVNames ++ repeat "unknown") dcvs
692
        formatted = map (\(header, val) ->
693
                             printf "%s=%.8f" header val::String) hd
694
    in intercalate ", " formatted
695

    
696
-- | Convert a placement into a list of OpCodes (basically a job).
697
iMoveToJob :: String -> Node.List -> Instance.List
698
          -> Idx -> IMove -> [OpCodes.OpCode]
699
iMoveToJob csf nl il idx move =
700
    let inst = Container.find idx il
701
        iname = Instance.name inst ++ csf
702
        lookNode n = Just (Container.nameOf nl n ++ csf)
703
        opF = if Instance.running inst
704
              then OpCodes.OpMigrateInstance iname True False
705
              else OpCodes.OpFailoverInstance iname False
706
        opR n = OpCodes.OpReplaceDisks iname (lookNode n)
707
                OpCodes.ReplaceNewSecondary [] Nothing
708
    in case move of
709
         Failover -> [ opF ]
710
         ReplacePrimary np -> [ opF, opR np, opF ]
711
         ReplaceSecondary ns -> [ opR ns ]
712
         ReplaceAndFailover np -> [ opR np, opF ]
713
         FailoverAndReplace ns -> [ opF, opR ns ]