Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 30ff0c73

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

    
190
-- | Compute the mem and disk covariance.
191
compDetailedCV :: Node.List -> [Double]
192
compDetailedCV nl =
193
    let
194
        all_nodes = Container.elems nl
195
        (offline, nodes) = partition Node.offline all_nodes
196
        mem_l = map Node.pMem nodes
197
        dsk_l = map Node.pDsk nodes
198
        mem_cv = varianceCoeff mem_l
199
        dsk_cv = varianceCoeff dsk_l
200
        n1_l = length $ filter Node.failN1 nodes
201
        n1_score = fromIntegral n1_l /
202
                   fromIntegral (length nodes)::Double
203
        res_l = map Node.pRem nodes
204
        res_cv = varianceCoeff res_l
205
        offline_inst = sum . map (\n -> (length . Node.pList $ n) +
206
                                        (length . Node.sList $ n)) $ offline
207
        online_inst = sum . map (\n -> (length . Node.pList $ n) +
208
                                       (length . Node.sList $ n)) $ nodes
209
        off_score = if offline_inst == 0
210
                    then 0::Double
211
                    else fromIntegral offline_inst /
212
                         fromIntegral (offline_inst + online_inst)::Double
213
        cpu_l = map Node.pCpu nodes
214
        cpu_cv = varianceCoeff cpu_l
215
        (c_load, m_load, d_load, n_load) = unzip4 $
216
            map (\n ->
217
                     let DynUtil c1 m1 d1 n1 = Node.utilLoad n
218
                         DynUtil c2 m2 d2 n2 = Node.utilPool n
219
                     in (c1/c2, m1/m2, d1/d2, n1/n2)
220
                ) nodes
221
    in [ mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv
222
       , varianceCoeff c_load, varianceCoeff m_load
223
       , varianceCoeff d_load, varianceCoeff n_load]
224

    
225
-- | Compute the /total/ variance.
226
compCV :: Node.List -> Double
227
compCV = sum . compDetailedCV
228

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

    
233
-- * hbal functions
234

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

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

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

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

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

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

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

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

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

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

    
390
possibleMoves False tdx =
391
    [ReplaceSecondary tdx,
392
     ReplaceAndFailover tdx]
393

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

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

    
439
-- | Run a balance move
440

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

    
464
-- * Allocation functions
465

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

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

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

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

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

    
516
tryAlloc _ _ _ reqn = fail $ "Unsupported number of allocation \
517
                             \destinations required (" ++ show reqn ++
518
                                               "), only two supported"
519

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

    
543
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
544
                                \destinations required (" ++ show reqn ++
545
                                                  "), only one supported"
546

    
547
-- * Formatting functions
548

    
549
-- | Given the original and final nodes, computes the relocation description.
550
computeMoves :: Instance.Instance -- ^ The instance to be moved
551
             -> String -- ^ The instance name
552
             -> IMove  -- ^ The move being performed
553
             -> String -- ^ New primary
554
             -> String -- ^ New secondary
555
             -> (String, [String])
556
                -- ^ Tuple of moves and commands list; moves is containing
557
                -- either @/f/@ for failover or @/r:name/@ for replace
558
                -- secondary, while the command list holds gnt-instance
559
                -- commands (without that prefix), e.g \"@failover instance1@\"
560
computeMoves i inam mv c d =
561
    case mv of
562
      Failover -> ("f", [mig])
563
      FailoverAndReplace _ -> (printf "f r:%s" d, [mig, rep d])
564
      ReplaceSecondary _ -> (printf "r:%s" d, [rep d])
565
      ReplaceAndFailover _ -> (printf "r:%s f" c, [rep c, mig])
566
      ReplacePrimary _ -> (printf "f r:%s f" c, [mig, rep c, mig])
567
    where morf = if Instance.running i then "migrate" else "failover"
568
          mig = printf "%s -f %s" morf inam::String
569
          rep n = printf "replace-disks -n %s %s" n inam
570

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

    
599
-- | Return the instance and involved nodes in an instance move.
600
involvedNodes :: Instance.List -> Placement -> [Ndx]
601
involvedNodes il plc =
602
    let (i, np, ns, _, _) = plc
603
        inst = Container.find i il
604
        op = Instance.pNode inst
605
        os = Instance.sNode inst
606
    in nub [np, ns, op, os]
607

    
608
-- | Inner function for splitJobs, that either appends the next job to
609
-- the current jobset, or starts a new jobset.
610
mergeJobs :: ([JobSet], [Ndx]) -> MoveJob -> ([JobSet], [Ndx])
611
mergeJobs ([], _) n@(ndx, _, _, _) = ([[n]], ndx)
612
mergeJobs (cjs@(j:js), nbuf) n@(ndx, _, _, _)
613
    | null (ndx `intersect` nbuf) = ((n:j):js, ndx ++ nbuf)
614
    | otherwise = ([n]:cjs, ndx)
615

    
616
-- | Break a list of moves into independent groups. Note that this
617
-- will reverse the order of jobs.
618
splitJobs :: [MoveJob] -> [JobSet]
619
splitJobs = fst . foldl mergeJobs ([], [])
620

    
621
-- | Given a list of commands, prefix them with @gnt-instance@ and
622
-- also beautify the display a little.
623
formatJob :: Int -> Int -> (Int, MoveJob) -> [String]
624
formatJob jsn jsl (sn, (_, _, _, cmds)) =
625
    let out =
626
            printf "  echo job %d/%d" jsn sn:
627
            printf "  check":
628
            map ("  gnt-instance " ++) cmds
629
    in if sn == 1
630
       then ["", printf "echo jobset %d, %d jobs" jsn jsl] ++ out
631
       else out
632

    
633
-- | Given a list of commands, prefix them with @gnt-instance@ and
634
-- also beautify the display a little.
635
formatCmds :: [JobSet] -> String
636
formatCmds =
637
    unlines .
638
    concatMap (\(jsn, js) -> concatMap (formatJob jsn (length js))
639
                             (zip [1..] js)) .
640
    zip [1..]
641

    
642
-- | Converts a solution to string format.
643
printSolution :: Node.List
644
              -> Instance.List
645
              -> [Placement]
646
              -> ([String], [[String]])
647
printSolution nl il sol =
648
    let
649
        nmlen = Container.maxNameLen nl
650
        imlen = Container.maxNameLen il
651
    in
652
      unzip $ zipWith (printSolutionLine nl il nmlen imlen) sol [1..]
653

    
654
-- | Print the node list.
655
printNodes :: Node.List -> String
656
printNodes nl =
657
    let snl = sortBy (compare `on` Node.idx) (Container.elems nl)
658
        header = ["F", "Name"
659
                 , "t_mem", "n_mem", "i_mem", "x_mem", "f_mem", "r_mem"
660
                 , "t_dsk", "f_dsk", "pcpu", "vcpu", "pri",  "sec"
661
                 , "p_fmem", "p_fdsk", "r_cpu"
662
                 , "lCpu", "lMem", "lDsk", "lNet" ]
663
        isnum = False:False:repeat True
664
    in unlines . map ((:) ' ' .  intercalate " ") $
665
       formatTable (header:map Node.list snl) isnum
666

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

    
693
-- | Shows statistics for a given node list.
694
printStats :: Node.List -> String
695
printStats nl =
696
    let dcvs = compDetailedCV nl
697
        hd = zip (detailedCVNames ++ repeat "unknown") dcvs
698
        formatted = map (\(header, val) ->
699
                             printf "%s=%.8f" header val::String) hd
700
    in intercalate ", " formatted
701

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