Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 7e7f6ca2

History | View | Annotate | Download (32 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
module Ganeti.HTools.Cluster
9
    (
10
     -- * Types
11
     NodeList
12
    , InstanceList
13
    , NameList
14
    , Placement
15
    , Solution(..)
16
    , Table(..)
17
    , Removal
18
    , Score
19
    -- * Generic functions
20
    , totalResources
21
    -- * First phase functions
22
    , computeBadItems
23
    -- * Second phase functions
24
    , computeSolution
25
    , applySolution
26
    , printSolution
27
    , printSolutionLine
28
    , formatCmds
29
    , printNodes
30
    -- * Balacing functions
31
    , checkMove
32
    , compCV
33
    , printStats
34
    -- * Loading functions
35
    , loadData
36
    , checkData
37
    ) where
38

    
39
import Data.List
40
import Data.Maybe (isNothing, fromJust)
41
import Text.Printf (printf)
42
import Data.Function
43
import Control.Monad
44

    
45
import qualified Ganeti.HTools.Container as Container
46
import qualified Ganeti.HTools.Instance as Instance
47
import qualified Ganeti.HTools.Node as Node
48
import Ganeti.HTools.Utils
49

    
50
type NodeList = Container.Container Node.Node
51
type InstanceList = Container.Container Instance.Instance
52
-- | The type used to hold idx-to-name mappings
53
type NameList = [(Int, String)]
54
-- | A separate name for the cluster score type
55
type Score = Double
56

    
57
-- | The description of an instance placement.
58
type Placement = (Int, Int, Int, Score)
59

    
60
{- | A cluster solution described as the solution delta and the list
61
of placements.
62

    
63
-}
64
data Solution = Solution Int [Placement]
65
                deriving (Eq, Ord, Show)
66

    
67
-- | Returns the delta of a solution or -1 for Nothing
68
solutionDelta :: Maybe Solution -> Int
69
solutionDelta sol = case sol of
70
                      Just (Solution d _) -> d
71
                      _ -> -1
72

    
73
-- | A removal set.
74
data Removal = Removal NodeList [Instance.Instance]
75

    
76
-- | An instance move definition
77
data IMove = Failover                -- ^ Failover the instance (f)
78
           | ReplacePrimary Int      -- ^ Replace primary (f, r:np, f)
79
           | ReplaceSecondary Int    -- ^ Replace secondary (r:ns)
80
           | ReplaceAndFailover Int  -- ^ Replace secondary, failover (r:np, f)
81
           | FailoverAndReplace Int  -- ^ Failover, replace secondary (f, r:ns)
82
             deriving (Show)
83

    
84
-- | The complete state for the balancing solution
85
data Table = Table NodeList InstanceList Score [Placement]
86
             deriving (Show)
87

    
88
-- | Constant node index for a non-moveable instance
89
noSecondary :: Int
90
noSecondary = -1
91

    
92
-- General functions
93

    
94
-- | Cap the removal list if needed.
95
capRemovals :: [a] -> Int -> [a]
96
capRemovals removals max_removals =
97
    if max_removals > 0 then
98
        take max_removals removals
99
    else
100
        removals
101

    
102
-- | Check if the given node list fails the N+1 check.
103
verifyN1Check :: [Node.Node] -> Bool
104
verifyN1Check nl = any Node.failN1 nl
105

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

    
110
{-| Add an instance and return the new node and instance maps. -}
111
addInstance :: NodeList -> Instance.Instance ->
112
               Node.Node -> Node.Node -> Maybe NodeList
113
addInstance nl idata pri sec =
114
  let pdx = Node.idx pri
115
      sdx = Node.idx sec
116
  in do
117
      pnode <- Node.addPri pri idata
118
      snode <- Node.addSec sec idata pdx
119
      new_nl <- return $ Container.addTwo sdx snode
120
                         pdx pnode nl
121
      return new_nl
122

    
123
-- | Remove an instance and return the new node and instance maps.
124
removeInstance :: NodeList -> Instance.Instance -> NodeList
125
removeInstance nl idata =
126
  let pnode = Instance.pnode idata
127
      snode = Instance.snode idata
128
      pn = Container.find pnode nl
129
      sn = Container.find snode nl
130
      new_nl = Container.addTwo
131
               pnode (Node.removePri pn idata)
132
               snode (Node.removeSec sn idata) nl in
133
  new_nl
134

    
135
-- | Remove an instance and return the new node map.
136
removeInstances :: NodeList -> [Instance.Instance] -> NodeList
137
removeInstances = foldl' removeInstance
138

    
139
-- | Compute the total free disk and memory in the cluster.
140
totalResources :: Container.Container Node.Node -> (Int, Int)
141
totalResources nl =
142
    foldl'
143
    (\ (mem, dsk) node -> (mem + (Node.f_mem node),
144
                           dsk + (Node.f_dsk node)))
145
    (0, 0) (Container.elems nl)
146

    
147
{- | Compute a new version of a cluster given a solution.
148

    
149
This is not used for computing the solutions, but for applying a
150
(known-good) solution to the original cluster for final display.
151

    
152
It first removes the relocated instances after which it places them on
153
their new nodes.
154

    
155
 -}
156
applySolution :: NodeList -> InstanceList -> [Placement] -> NodeList
157
applySolution nl il sol =
158
    let odxes = map (\ (a, b, c, _) -> (Container.find a il,
159
                                        Node.idx (Container.find b nl),
160
                                        Node.idx (Container.find c nl))
161
                    ) sol
162
        idxes = (\ (x, _, _) -> x) (unzip3 odxes)
163
        nc = removeInstances nl idxes
164
    in
165
      foldl' (\ nz (a, b, c) ->
166
                 let new_p = Container.find b nz
167
                     new_s = Container.find c nz in
168
                 fromJust (addInstance nz a new_p new_s)
169
           ) nc odxes
170

    
171

    
172
-- First phase functions
173

    
174
{- | Given a list 1,2,3..n build a list of pairs [(1, [2..n]), (2,
175
    [3..n]), ...]
176

    
177
-}
178
genParts :: [a] -> Int -> [(a, [a])]
179
genParts l count =
180
    case l of
181
      [] -> []
182
      x:xs ->
183
          if length l < count then
184
              []
185
          else
186
              (x, xs) : (genParts xs count)
187

    
188
-- | Generates combinations of count items from the names list.
189
genNames :: Int -> [b] -> [[b]]
190
genNames count1 names1 =
191
  let aux_fn count names current =
192
          case count of
193
            0 -> [current]
194
            _ ->
195
                concatMap
196
                (\ (x, xs) -> aux_fn (count - 1) xs (x:current))
197
                (genParts names count)
198
  in
199
    aux_fn count1 names1 []
200

    
201
{- | Computes the pair of bad nodes and instances.
202

    
203
The bad node list is computed via a simple 'verifyN1' check, and the
204
bad instance list is the list of primary and secondary instances of
205
those nodes.
206

    
207
-}
208
computeBadItems :: NodeList -> InstanceList ->
209
                   ([Node.Node], [Instance.Instance])
210
computeBadItems nl il =
211
  let bad_nodes = verifyN1 $ filter (not . Node.offline) $ Container.elems nl
212
      bad_instances = map (\idx -> Container.find idx il) $
213
                      sort $ nub $ concat $
214
                      map (\ n -> (Node.slist n) ++ (Node.plist n)) bad_nodes
215
  in
216
    (bad_nodes, bad_instances)
217

    
218

    
219
{- | Checks if removal of instances results in N+1 pass.
220

    
221
Note: the check removal cannot optimize by scanning only the affected
222
nodes, since the cluster is known to be not healthy; only the check
223
placement can make this shortcut.
224

    
225
-}
226
checkRemoval :: NodeList -> [Instance.Instance] -> Maybe Removal
227
checkRemoval nl victims =
228
  let nx = removeInstances nl victims
229
      failN1 = verifyN1Check (Container.elems nx)
230
  in
231
    if failN1 then
232
      Nothing
233
    else
234
      Just $ Removal nx victims
235

    
236

    
237
-- | Computes the removals list for a given depth
238
computeRemovals :: NodeList
239
                 -> [Instance.Instance]
240
                 -> Int
241
                 -> [Maybe Removal]
242
computeRemovals nl bad_instances depth =
243
    map (checkRemoval nl) $ genNames depth bad_instances
244

    
245
-- Second phase functions
246

    
247
-- | Single-node relocation cost
248
nodeDelta :: Int -> Int -> Int -> Int
249
nodeDelta i p s =
250
    if i == p || i == s then
251
        0
252
    else
253
        1
254

    
255
{-| Compute best solution.
256

    
257
    This function compares two solutions, choosing the minimum valid
258
    solution.
259
-}
260
compareSolutions :: Maybe Solution -> Maybe Solution -> Maybe Solution
261
compareSolutions a b = case (a, b) of
262
  (Nothing, x) -> x
263
  (x, Nothing) -> x
264
  (x, y) -> min x y
265

    
266
-- | Compute best table. Note that the ordering of the arguments is important.
267
compareTables :: Table -> Table -> Table
268
compareTables a@(Table _ _ a_cv _) b@(Table _ _ b_cv _ ) =
269
    if a_cv > b_cv then b else a
270

    
271
-- | Check if a given delta is worse then an existing solution.
272
tooHighDelta :: Maybe Solution -> Int -> Int -> Bool
273
tooHighDelta sol new_delta max_delta =
274
    if new_delta > max_delta && max_delta >=0 then
275
        True
276
    else
277
        case sol of
278
          Nothing -> False
279
          Just (Solution old_delta _) -> old_delta <= new_delta
280

    
281
{-| Check if placement of instances still keeps the cluster N+1 compliant.
282

    
283
    This is the workhorse of the allocation algorithm: given the
284
    current node and instance maps, the list of instances to be
285
    placed, and the current solution, this will return all possible
286
    solution by recursing until all target instances are placed.
287

    
288
-}
289
checkPlacement :: NodeList            -- ^ The current node list
290
               -> [Instance.Instance] -- ^ List of instances still to place
291
               -> [Placement]         -- ^ Partial solution until now
292
               -> Int                 -- ^ The delta of the partial solution
293
               -> Maybe Solution      -- ^ The previous solution
294
               -> Int                 -- ^ Abort if the we go above this delta
295
               -> Maybe Solution      -- ^ The new solution
296
checkPlacement nl victims current current_delta prev_sol max_delta =
297
  let target = head victims
298
      opdx = Instance.pnode target
299
      osdx = Instance.snode target
300
      vtail = tail victims
301
      have_tail = (length vtail) > 0
302
      nodes = Container.elems nl
303
      iidx = Instance.idx target
304
  in
305
    foldl'
306
    (\ accu_p pri ->
307
         let
308
             pri_idx = Node.idx pri
309
             upri_delta = current_delta + nodeDelta pri_idx opdx osdx
310
             new_pri = Node.addPri pri target
311
             fail_delta1 = tooHighDelta accu_p upri_delta max_delta
312
         in
313
           if fail_delta1 || isNothing(new_pri) then accu_p
314
           else let pri_nl = Container.add pri_idx (fromJust new_pri) nl in
315
                foldl'
316
                (\ accu sec ->
317
                     let
318
                         sec_idx = Node.idx sec
319
                         upd_delta = upri_delta +
320
                                     nodeDelta sec_idx opdx osdx
321
                         fail_delta2 = tooHighDelta accu upd_delta max_delta
322
                         new_sec = Node.addSec sec target pri_idx
323
                     in
324
                       if sec_idx == pri_idx || fail_delta2 ||
325
                          isNothing new_sec then accu
326
                       else let
327
                           nx = Container.add sec_idx (fromJust new_sec) pri_nl
328
                           upd_cv = compCV nx
329
                           plc = (iidx, pri_idx, sec_idx, upd_cv)
330
                           c2 = plc:current
331
                           result =
332
                               if have_tail then
333
                                   checkPlacement nx vtail c2 upd_delta
334
                                                  accu max_delta
335
                               else
336
                                   Just (Solution upd_delta c2)
337
                      in compareSolutions accu result
338
                ) accu_p nodes
339
    ) prev_sol nodes
340

    
341
-- | Apply a move
342
applyMove :: NodeList -> Instance.Instance
343
          -> IMove -> (Maybe NodeList, Instance.Instance, Int, Int)
344
-- Failover (f)
345
applyMove nl inst Failover =
346
    let old_pdx = Instance.pnode inst
347
        old_sdx = Instance.snode inst
348
        old_p = Container.find old_pdx nl
349
        old_s = Container.find old_sdx nl
350
        int_p = Node.removePri old_p inst
351
        int_s = Node.removeSec old_s inst
352
        new_nl = do -- Maybe monad
353
          new_p <- Node.addPri int_s inst
354
          new_s <- Node.addSec int_p inst old_sdx
355
          return $ Container.addTwo old_pdx new_s old_sdx new_p nl
356
    in (new_nl, Instance.setBoth inst old_sdx old_pdx, old_sdx, old_pdx)
357

    
358
-- Replace the primary (f:, r:np, f)
359
applyMove nl inst (ReplacePrimary new_pdx) =
360
    let old_pdx = Instance.pnode inst
361
        old_sdx = Instance.snode inst
362
        old_p = Container.find old_pdx nl
363
        old_s = Container.find old_sdx nl
364
        tgt_n = Container.find new_pdx nl
365
        int_p = Node.removePri old_p inst
366
        int_s = Node.removeSec old_s inst
367
        new_nl = do -- Maybe monad
368
          new_p <- Node.addPri tgt_n inst
369
          new_s <- Node.addSec int_s inst new_pdx
370
          return $ Container.add new_pdx new_p $
371
                 Container.addTwo old_pdx int_p old_sdx new_s nl
372
    in (new_nl, Instance.setPri inst new_pdx, new_pdx, old_sdx)
373

    
374
-- Replace the secondary (r:ns)
375
applyMove nl inst (ReplaceSecondary new_sdx) =
376
    let old_pdx = Instance.pnode inst
377
        old_sdx = Instance.snode inst
378
        old_s = Container.find old_sdx nl
379
        tgt_n = Container.find new_sdx nl
380
        int_s = Node.removeSec old_s inst
381
        new_nl = Node.addSec tgt_n inst old_pdx >>=
382
                 \new_s -> return $ Container.addTwo new_sdx
383
                           new_s old_sdx int_s nl
384
    in (new_nl, Instance.setSec inst new_sdx, old_pdx, new_sdx)
385

    
386
-- Replace the secondary and failover (r:np, f)
387
applyMove nl inst (ReplaceAndFailover new_pdx) =
388
    let old_pdx = Instance.pnode inst
389
        old_sdx = Instance.snode inst
390
        old_p = Container.find old_pdx nl
391
        old_s = Container.find old_sdx nl
392
        tgt_n = Container.find new_pdx nl
393
        int_p = Node.removePri old_p inst
394
        int_s = Node.removeSec old_s inst
395
        new_nl = do -- Maybe monad
396
          new_p <- Node.addPri tgt_n inst
397
          new_s <- Node.addSec int_p inst new_pdx
398
          return $ Container.add new_pdx new_p $
399
                 Container.addTwo old_pdx new_s old_sdx int_s nl
400
    in (new_nl, Instance.setBoth inst new_pdx old_pdx, new_pdx, old_pdx)
401

    
402
-- Failver and replace the secondary (f, r:ns)
403
applyMove nl inst (FailoverAndReplace new_sdx) =
404
    let old_pdx = Instance.pnode inst
405
        old_sdx = Instance.snode inst
406
        old_p = Container.find old_pdx nl
407
        old_s = Container.find old_sdx nl
408
        tgt_n = Container.find new_sdx nl
409
        int_p = Node.removePri old_p inst
410
        int_s = Node.removeSec old_s inst
411
        new_nl = do -- Maybe monad
412
          new_p <- Node.addPri int_s inst
413
          new_s <- Node.addSec tgt_n inst old_sdx
414
          return $ Container.add new_sdx new_s $
415
                 Container.addTwo old_sdx new_p old_pdx int_p nl
416
    in (new_nl, Instance.setBoth inst old_sdx new_sdx, old_sdx, new_sdx)
417

    
418
checkSingleStep :: Table -- ^ The original table
419
                -> Instance.Instance -- ^ The instance to move
420
                -> Table -- ^ The current best table
421
                -> IMove -- ^ The move to apply
422
                -> Table -- ^ The final best table
423
checkSingleStep ini_tbl target cur_tbl move =
424
    let
425
        Table ini_nl ini_il _ ini_plc = ini_tbl
426
        (tmp_nl, new_inst, pri_idx, sec_idx) = applyMove ini_nl target move
427
    in
428
      if isNothing tmp_nl then cur_tbl
429
      else
430
          let tgt_idx = Instance.idx target
431
              upd_nl = fromJust tmp_nl
432
              upd_cvar = compCV upd_nl
433
              upd_il = Container.add tgt_idx new_inst ini_il
434
              upd_plc = (tgt_idx, pri_idx, sec_idx, upd_cvar):ini_plc
435
              upd_tbl = Table upd_nl upd_il upd_cvar upd_plc
436
          in
437
            compareTables cur_tbl upd_tbl
438

    
439
-- | Given the status of the current secondary as a valid new node
440
-- and the current candidate target node,
441
-- generate the possible moves for a instance.
442
possibleMoves :: Bool -> Int -> [IMove]
443
possibleMoves True tdx =
444
    [ReplaceSecondary tdx,
445
     ReplaceAndFailover tdx,
446
     ReplacePrimary tdx,
447
     FailoverAndReplace tdx]
448

    
449
possibleMoves False tdx =
450
    [ReplaceSecondary tdx,
451
     ReplaceAndFailover tdx]
452

    
453
-- | Compute the best move for a given instance.
454
checkInstanceMove :: [Int]             -- Allowed target node indices
455
                  -> Table             -- Original table
456
                  -> Instance.Instance -- Instance to move
457
                  -> Table             -- Best new table for this instance
458
checkInstanceMove nodes_idx ini_tbl target =
459
    let
460
        opdx = Instance.pnode target
461
        osdx = Instance.snode target
462
        nodes = filter (\idx -> idx /= opdx && idx /= osdx) nodes_idx
463
        use_secondary = elem osdx nodes_idx
464
        aft_failover = if use_secondary -- if allowed to failover
465
                       then checkSingleStep ini_tbl target ini_tbl Failover
466
                       else ini_tbl
467
        all_moves = concatMap (possibleMoves use_secondary) nodes
468
    in
469
      -- iterate over the possible nodes for this instance
470
      foldl' (checkSingleStep ini_tbl target) aft_failover all_moves
471

    
472
-- | Compute the best next move.
473
checkMove :: [Int]               -- ^ Allowed target node indices
474
          -> Table               -- ^ The current solution
475
          -> [Instance.Instance] -- ^ List of instances still to move
476
          -> Table               -- ^ The new solution
477
checkMove nodes_idx ini_tbl victims =
478
    let Table _ _ _ ini_plc = ini_tbl
479
        -- iterate over all instances, computing the best move
480
        best_tbl =
481
            foldl'
482
            (\ step_tbl elem ->
483
                 if Instance.snode elem == noSecondary then step_tbl
484
                    else compareTables step_tbl $
485
                         checkInstanceMove nodes_idx ini_tbl elem)
486
            ini_tbl victims
487
        Table _ _ _ best_plc = best_tbl
488
    in
489
      if length best_plc == length ini_plc then -- no advancement
490
          ini_tbl
491
      else
492
          best_tbl
493

    
494
{- | Auxiliary function for solution computation.
495

    
496
We write this in an explicit recursive fashion in order to control
497
early-abort in case we have met the min delta. We can't use foldr
498
instead of explicit recursion since we need the accumulator for the
499
abort decision.
500

    
501
-}
502
advanceSolution :: [Maybe Removal] -- ^ The removal to process
503
                -> Int             -- ^ Minimum delta parameter
504
                -> Int             -- ^ Maximum delta parameter
505
                -> Maybe Solution  -- ^ Current best solution
506
                -> Maybe Solution  -- ^ New best solution
507
advanceSolution [] _ _ sol = sol
508
advanceSolution (Nothing:xs) m n sol = advanceSolution xs m n sol
509
advanceSolution ((Just (Removal nx removed)):xs) min_d max_d prev_sol =
510
    let new_sol = checkPlacement nx removed [] 0 prev_sol max_d
511
        new_delta = solutionDelta $! new_sol
512
    in
513
      if new_delta >= 0 && new_delta <= min_d then
514
          new_sol
515
      else
516
          advanceSolution xs min_d max_d new_sol
517

    
518
-- | Computes the placement solution.
519
solutionFromRemovals :: [Maybe Removal] -- ^ The list of (possible) removals
520
                     -> Int             -- ^ Minimum delta parameter
521
                     -> Int             -- ^ Maximum delta parameter
522
                     -> Maybe Solution  -- ^ The best solution found
523
solutionFromRemovals removals min_delta max_delta =
524
    advanceSolution removals min_delta max_delta Nothing
525

    
526
{- | Computes the solution at the given depth.
527

    
528
This is a wrapper over both computeRemovals and
529
solutionFromRemovals. In case we have no solution, we return Nothing.
530

    
531
-}
532
computeSolution :: NodeList        -- ^ The original node data
533
                -> [Instance.Instance] -- ^ The list of /bad/ instances
534
                -> Int             -- ^ The /depth/ of removals
535
                -> Int             -- ^ Maximum number of removals to process
536
                -> Int             -- ^ Minimum delta parameter
537
                -> Int             -- ^ Maximum delta parameter
538
                -> Maybe Solution  -- ^ The best solution found (or Nothing)
539
computeSolution nl bad_instances depth max_removals min_delta max_delta =
540
  let
541
      removals = computeRemovals nl bad_instances depth
542
      removals' = capRemovals removals max_removals
543
  in
544
    solutionFromRemovals removals' min_delta max_delta
545

    
546
-- Solution display functions (pure)
547

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

    
586
                else {- Nothing in common -}
587
                    (printf "r:%s f r:%s" c d,
588
                     [printf "replace-disks -n %s %s" c i,
589
                      printf "migrate -f %s" i,
590
                      printf "replace-disks -n %s %s" d i])
591

    
592
{-| Converts a placement to string format -}
593
printSolutionLine :: InstanceList
594
              -> NameList
595
              -> NameList
596
              -> Int
597
              -> Int
598
              -> Placement
599
              -> Int
600
              -> (String, [String])
601
printSolutionLine il ktn kti nmlen imlen plc pos =
602
    let
603
        pmlen = (2*nmlen + 1)
604
        (i, p, s, c) = plc
605
        inst = Container.find i il
606
        inam = fromJust $ lookup (Instance.idx inst) kti
607
        npri = fromJust $ lookup p ktn
608
        nsec = fromJust $ lookup s ktn
609
        opri = fromJust $ lookup (Instance.pnode inst) ktn
610
        osec = fromJust $ lookup (Instance.snode inst) ktn
611
        (moves, cmds) =  computeMoves inam opri osec npri nsec
612
        ostr = (printf "%s:%s" opri osec)::String
613
        nstr = (printf "%s:%s" npri nsec)::String
614
    in
615
      (printf "  %3d. %-*s %-*s => %-*s %.8f a=%s"
616
       pos imlen inam pmlen ostr
617
       pmlen nstr c moves,
618
       cmds)
619

    
620
formatCmds :: [[String]] -> String
621
formatCmds cmd_strs =
622
    unlines $
623
    concat $ map (\(a, b) ->
624
        (printf "echo step %d" (a::Int)):
625
        (printf "check"):
626
        (map ("gnt-instance " ++) b)) $
627
        zip [1..] cmd_strs
628

    
629
{-| Converts a solution to string format -}
630
printSolution :: InstanceList
631
              -> NameList
632
              -> NameList
633
              -> [Placement]
634
              -> ([String], [[String]])
635
printSolution il ktn kti sol =
636
    let
637
        mlen_fn = maximum . (map length) . snd . unzip
638
        imlen = mlen_fn kti
639
        nmlen = mlen_fn ktn
640
    in
641
      unzip $ map (uncurry $ printSolutionLine il ktn kti nmlen imlen) $
642
            zip sol [1..]
643

    
644
-- | Print the node list.
645
printNodes :: NameList -> NodeList -> String
646
printNodes ktn nl =
647
    let snl = sortBy (compare `on` Node.idx) (Container.elems nl)
648
        snl' = map (\ n -> ((fromJust $ lookup (Node.idx n) ktn), n)) snl
649
        m_name = maximum . (map length) . fst . unzip $ snl'
650
        helper = Node.list m_name
651
        header = printf
652
                 "%2s %-*s %5s %5s %5s %5s %5s %5s %5s %5s %3s %3s %7s %7s"
653
                 " F" m_name "Name"
654
                 "t_mem" "n_mem" "i_mem" "x_mem" "f_mem" "r_mem"
655
                 "t_dsk" "f_dsk"
656
                 "pri" "sec" "p_fmem" "p_fdsk"
657
    in unlines $ (header:map (uncurry helper) snl')
658

    
659
-- | Compute the mem and disk covariance.
660
compDetailedCV :: NodeList -> (Double, Double, Double, Double, Double)
661
compDetailedCV nl =
662
    let
663
        all_nodes = Container.elems nl
664
        (offline, nodes) = partition Node.offline all_nodes
665
        mem_l = map Node.p_mem nodes
666
        dsk_l = map Node.p_dsk nodes
667
        mem_cv = varianceCoeff mem_l
668
        dsk_cv = varianceCoeff dsk_l
669
        n1_l = length $ filter Node.failN1 nodes
670
        n1_score = (fromIntegral n1_l) / (fromIntegral $ length nodes)
671
        res_l = map Node.p_rem nodes
672
        res_cv = varianceCoeff res_l
673
        offline_inst = sum . map (\n -> (length . Node.plist $ n) +
674
                                        (length . Node.slist $ n)) $ offline
675
        online_inst = sum . map (\n -> (length . Node.plist $ n) +
676
                                       (length . Node.slist $ n)) $ nodes
677
        off_score = (fromIntegral offline_inst) /
678
                    (fromIntegral $ online_inst + offline_inst)
679
    in (mem_cv, dsk_cv, n1_score, res_cv, off_score)
680

    
681
-- | Compute the 'total' variance.
682
compCV :: NodeList -> Double
683
compCV nl =
684
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score) = compDetailedCV nl
685
    in mem_cv + dsk_cv + n1_score + res_cv + off_score
686

    
687
printStats :: NodeList -> String
688
printStats nl =
689
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score) = compDetailedCV nl
690
    in printf "f_mem=%.8f, r_mem=%.8f, f_dsk=%.8f, n1=%.3f, uf=%.3f"
691
       mem_cv res_cv dsk_cv n1_score off_score
692

    
693
-- Balancing functions
694

    
695
-- Loading functions
696

    
697
{- | Convert newline and delimiter-separated text.
698

    
699
This function converts a text in tabular format as generated by
700
@gnt-instance list@ and @gnt-node list@ to a list of objects using a
701
supplied conversion function.
702

    
703
-}
704
loadTabular :: (Monad m) => String -> ([String] -> m (String, a))
705
            -> (a -> Int -> a) -> m ([(String, Int)], [(Int, a)])
706
loadTabular text_data convert_fn set_fn = do
707
  let lines_data = lines text_data
708
      rows = map (sepSplit '|') lines_data
709
  kerows <- mapM convert_fn rows
710
  let idxrows = map (\ (idx, (k, v)) -> ((k, idx), (idx, set_fn v idx)))
711
                (zip [0..] kerows)
712
  return $ unzip idxrows
713

    
714
-- | For each instance, add its index to its primary and secondary nodes
715
fixNodes :: [(Int, Node.Node)]
716
         -> [(Int, Instance.Instance)]
717
         -> [(Int, Node.Node)]
718
fixNodes nl il =
719
    foldl' (\accu (idx, inst) ->
720
                let
721
                    assocEqual = (\ (i, _) (j, _) -> i == j)
722
                    pdx = Instance.pnode inst
723
                    sdx = Instance.snode inst
724
                    pold = fromJust $ lookup pdx accu
725
                    pnew = Node.setPri pold idx
726
                    ac1 = deleteBy assocEqual (pdx, pold) accu
727
                    ac2 = (pdx, pnew):ac1
728
                in
729
                  if sdx /= noSecondary then
730
                      let
731
                          sold = fromJust $ lookup sdx accu
732
                          snew = Node.setSec sold idx
733
                          ac3 = deleteBy assocEqual (sdx, sold) ac2
734
                          ac4 = (sdx, snew):ac3
735
                      in ac4
736
                  else
737
                      ac2
738
           ) nl il
739

    
740
-- | Compute the longest common suffix of a NameList list that
741
-- | starts with a dot
742
longestDomain :: NameList -> String
743
longestDomain [] = ""
744
longestDomain ((_,x):xs) =
745
    let
746
        onlyStrings = snd $ unzip xs
747
    in
748
      foldr (\ suffix accu -> if all (isSuffixOf suffix) onlyStrings
749
                              then suffix
750
                              else accu)
751
      "" $ filter (isPrefixOf ".") (tails x)
752

    
753
-- | Remove tails from the (Int, String) lists
754
stripSuffix :: String -> NameList -> NameList
755
stripSuffix suffix lst =
756
    let sflen = length suffix in
757
    map (\ (key, name) -> (key, take ((length name) - sflen) name)) lst
758

    
759
-- | Safe 'read' function returning data encapsulated in a Result
760
tryRead :: (Monad m, Read a) => String -> String -> m a
761
tryRead name s =
762
    let sols = readsPrec 0 s
763
    in case sols of
764
         (v, ""):[] -> return v
765
         (_, e):[] -> fail $ name ++ ": leftover characters when parsing '"
766
                      ++ s ++ "': '" ++ e ++ "'"
767
         _ -> fail $ name ++ ": cannot parse string '" ++ s ++ "'"
768

    
769
-- | Lookups a node into an assoc list
770
lookupNode :: (Monad m) => String -> String -> [(String, Int)] -> m Int
771
lookupNode node inst ktn =
772
    case lookup node ktn of
773
      Nothing -> fail $ "Unknown node '" ++ node ++ "' for instance " ++ inst
774
      Just idx -> return idx
775

    
776
-- | Load a node from a field list
777
loadNode :: (Monad m) => [String] -> m (String, Node.Node)
778
loadNode (name:tm:nm:fm:td:fd:fo:[]) = do
779
  new_node <-
780
      if any (== "?") [tm,nm,fm,td,fd] || fo == "Y" then
781
          return $ Node.create 0 0 0 0 0 True
782
      else do
783
        vtm <- tryRead name tm
784
        vnm <- tryRead name nm
785
        vfm <- tryRead name fm
786
        vtd <- tryRead name td
787
        vfd <- tryRead name fd
788
        return $ Node.create vtm vnm vfm vtd vfd False
789
  return (name, new_node)
790
loadNode s = fail $ "Invalid/incomplete node data: '" ++ (show s) ++ "'"
791

    
792
-- | Load an instance from a field list
793
loadInst :: (Monad m) =>
794
            [(String, Int)] -> [String] -> m (String, Instance.Instance)
795
loadInst ktn (name:mem:dsk:status:pnode:snode:[]) = do
796
  pidx <- lookupNode pnode name ktn
797
  sidx <- (if null snode then return noSecondary
798
           else lookupNode snode name ktn)
799
  vmem <- tryRead name mem
800
  vdsk <- tryRead name dsk
801
  when (sidx == pidx) $ fail $ "Instance " ++ name ++
802
           " has same primary and secondary node - " ++ pnode
803
  let newinst = Instance.create vmem vdsk status pidx sidx
804
  return (name, newinst)
805
loadInst _ s = fail $ "Invalid/incomplete instance data: '" ++ (show s) ++ "'"
806

    
807
{-| Initializer function that loads the data from a node and list file
808
    and massages it into the correct format. -}
809
loadData :: String -- ^ Node data in text format
810
         -> String -- ^ Instance data in text format
811
         -> Result (Container.Container Node.Node,
812
                    Container.Container Instance.Instance,
813
                    String, NameList, NameList)
814
loadData ndata idata = do
815
  {- node file: name t_mem n_mem f_mem t_disk f_disk -}
816
  (ktn, nl) <- loadTabular ndata loadNode Node.setIdx
817
      {- instance file: name mem disk status pnode snode -}
818
  (kti, il) <- loadTabular idata (loadInst ktn) Instance.setIdx
819
  let
820
      nl2 = fixNodes nl il
821
      il3 = Container.fromAssocList il
822
      nl3 = Container.fromAssocList
823
            (map (\ (k, v) -> (k, Node.buildPeers v il3 (length nl2))) nl2)
824
      xtn = swapPairs ktn
825
      xti = swapPairs kti
826
      common_suffix = longestDomain (xti ++ xtn)
827
      stn = stripSuffix common_suffix xtn
828
      sti = stripSuffix common_suffix xti
829
  return (nl3, il3, common_suffix, stn, sti)
830

    
831
-- | Compute the amount of memory used by primary instances on a node.
832
nodeImem :: Node.Node -> InstanceList -> Int
833
nodeImem node il =
834
    let rfind = flip Container.find $ il
835
    in sum . map Instance.mem .
836
       map rfind $ Node.plist node
837

    
838
-- | Compute the amount of disk used by instances on a node (either primary
839
-- or secondary).
840
nodeIdsk :: Node.Node -> InstanceList -> Int
841
nodeIdsk node il =
842
    let rfind = flip Container.find $ il
843
    in sum . map Instance.dsk .
844
       map rfind $ (Node.plist node) ++ (Node.slist node)
845

    
846
-- | Check cluster data for consistency
847
checkData :: NodeList -> InstanceList -> NameList -> NameList
848
          -> ([String], NodeList)
849
checkData nl il ktn _ =
850
    Container.mapAccum
851
        (\ msgs node ->
852
             let nname = fromJust $ lookup (Node.idx node) ktn
853
                 nilst = map (flip Container.find $ il) (Node.plist node)
854
                 dilst = filter (not . Instance.running) nilst
855
                 adj_mem = sum . map Instance.mem $ dilst
856
                 delta_mem = (truncate $ Node.t_mem node)
857
                             - (Node.n_mem node)
858
                             - (Node.f_mem node)
859
                             - (nodeImem node il)
860
                             + adj_mem
861
                 delta_dsk = (truncate $ Node.t_dsk node)
862
                             - (Node.f_dsk node)
863
                             - (nodeIdsk node il)
864
                 newn = Node.setFmem (Node.setXmem node delta_mem)
865
                        (Node.f_mem node - adj_mem)
866
                 umsg1 = if delta_mem > 512 || delta_dsk > 1024
867
                         then [printf "node %s is missing %d MB ram \
868
                                     \and %d GB disk"
869
                                     nname delta_mem (delta_dsk `div` 1024)]
870
                         else []
871
             in (msgs ++ umsg1, newn)
872
        ) [] nl