Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 183a9c3d

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

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

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

    
73
-- * Types
74

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

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

    
81

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

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

    
106
-- * Utility functions
107

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

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

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

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

    
129
emptyCStats :: CStats
130
emptyCStats = CStats { csFmem = 0
131
                     , csFdsk = 0
132
                     , csAmem = 0
133
                     , csAdsk = 0
134
                     , csAcpu = 0
135
                     , csMmem = 0
136
                     , csMdsk = 0
137
                     , csMcpu = 0
138
                     , csImem = 0
139
                     , csIdsk = 0
140
                     , csIcpu = 0
141
                     , csTmem = 0
142
                     , csTdsk = 0
143
                     , csTcpu = 0
144
                     , csXmem = 0
145
                     , csNmem = 0
146
                     , csScore = 0
147
                     , csNinst = 0
148
                     }
149

    
150
updateCStats :: CStats -> Node.Node -> CStats
151
updateCStats cs node =
152
    let CStats { csFmem = x_fmem, csFdsk = x_fdsk,
153
                 csAmem = x_amem, csAcpu = x_acpu, csAdsk = x_adsk,
154
                 csMmem = x_mmem, csMdsk = x_mdsk, csMcpu = x_mcpu,
155
                 csImem = x_imem, csIdsk = x_idsk, csIcpu = x_icpu,
156
                 csTmem = x_tmem, csTdsk = x_tdsk, csTcpu = x_tcpu,
157
                 csXmem = x_xmem, csNmem = x_nmem, csNinst = x_ninst
158
               }
159
            = cs
160
        inc_amem = Node.fMem node - Node.rMem node
161
        inc_amem' = if inc_amem > 0 then inc_amem else 0
162
        inc_adsk = Node.availDisk node
163
        inc_imem = truncate (Node.tMem node) - Node.nMem node
164
                   - Node.xMem node - Node.fMem node
165
        inc_icpu = Node.uCpu node
166
        inc_idsk = truncate (Node.tDsk node) - Node.fDsk node
167

    
168
    in cs { csFmem = x_fmem + Node.fMem node
169
          , csFdsk = x_fdsk + Node.fDsk node
170
          , csAmem = x_amem + inc_amem'
171
          , csAdsk = x_adsk + inc_adsk
172
          , csAcpu = x_acpu
173
          , csMmem = max x_mmem inc_amem'
174
          , csMdsk = max x_mdsk inc_adsk
175
          , csMcpu = x_mcpu
176
          , csImem = x_imem + inc_imem
177
          , csIdsk = x_idsk + inc_idsk
178
          , csIcpu = x_icpu + inc_icpu
179
          , csTmem = x_tmem + Node.tMem node
180
          , csTdsk = x_tdsk + Node.tDsk node
181
          , csTcpu = x_tcpu + Node.tCpu node
182
          , csXmem = x_xmem + Node.xMem node
183
          , csNmem = x_nmem + Node.nMem node
184
          , csNinst = x_ninst + length (Node.pList node)
185
          }
186

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

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

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

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

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

    
238
-- * hbal functions
239

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

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

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

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

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

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

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

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

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

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

    
395
possibleMoves False tdx =
396
    [ReplaceSecondary tdx,
397
     ReplaceAndFailover tdx]
398

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

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

    
444
-- | Run a balance move
445

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

    
469
-- * Allocation functions
470

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

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

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

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

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

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

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

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

    
552
-- * Formatting functions
553

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

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

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

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

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

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

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

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

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

    
690
-- | Print the instance list.
691
printInsts :: Node.List -> Instance.List -> String
692
printInsts nl il =
693
    let sil = sortBy (compare `on` Instance.idx) (Container.elems il)
694
        m_name = maximum . map (length . Instance.name) $ sil
695
        m_nnm  = maximum . map (length . Node.name) $ Container.elems nl
696
        helper inst = printf "%2s %-*s %-*s %-*s"
697
                      "  " m_name (Instance.name inst)
698
                      m_nnm (Container.nameOf nl (Instance.pNode inst))
699
                      m_nnm (Container.nameOf nl (Instance.sNode inst))
700
        header = printf "%2s %-*s %-*s %-*s"
701
                 "  " m_name "Name" m_nnm "Pri_node" m_nnm "Sec_node"::String
702
    in unlines (header:map helper sil)
703

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

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