Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 7847a037

History | View | Annotate | Download (28.5 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
    -- * Generic functions
19
    , totalResources
20
    -- * First phase functions
21
    , computeBadItems
22
    -- * Second phase functions
23
    , computeSolution
24
    , applySolution
25
    , printSolution
26
    , printSolutionLine
27
    , formatCmds
28
    , printNodes
29
    -- * Balacing functions
30
    , checkMove
31
    , compCV
32
    , printStats
33
    -- * Loading functions
34
    , loadData
35
    ) where
36

    
37
import Data.List
38
import Data.Maybe (isNothing, fromJust)
39
import Text.Printf (printf)
40
import Data.Function
41

    
42
import qualified Ganeti.HTools.Container as Container
43
import qualified Ganeti.HTools.Instance as Instance
44
import qualified Ganeti.HTools.Node as Node
45
import Ganeti.HTools.Utils
46

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

    
54
-- | The description of an instance placement.
55
type Placement = (Int, Int, Int, Score)
56

    
57
{- | A cluster solution described as the solution delta and the list
58
of placements.
59

    
60
-}
61
data Solution = Solution Int [Placement]
62
                deriving (Eq, Ord, Show)
63

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

    
70
-- | A removal set.
71
data Removal = Removal NodeList [Instance.Instance]
72

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

    
81
-- | The complete state for the balancing solution
82
data Table = Table NodeList InstanceList Score [Placement]
83
             deriving (Show)
84

    
85
-- General functions
86

    
87
-- | Cap the removal list if needed.
88
capRemovals :: [a] -> Int -> [a]
89
capRemovals removals max_removals =
90
    if max_removals > 0 then
91
        take max_removals removals
92
    else
93
        removals
94

    
95
-- | Check if the given node list fails the N+1 check.
96
verifyN1Check :: [Node.Node] -> Bool
97
verifyN1Check nl = any Node.failN1 nl
98

    
99
-- | Verifies the N+1 status and return the affected nodes.
100
verifyN1 :: [Node.Node] -> [Node.Node]
101
verifyN1 nl = filter Node.failN1 nl
102

    
103
{-| Add an instance and return the new node and instance maps. -}
104
addInstance :: NodeList -> Instance.Instance ->
105
               Node.Node -> Node.Node -> Maybe NodeList
106
addInstance nl idata pri sec =
107
  let pdx = Node.idx pri
108
      sdx = Node.idx sec
109
  in do
110
      pnode <- Node.addPri pri idata
111
      snode <- Node.addSec sec idata pdx
112
      new_nl <- return $ Container.addTwo sdx snode
113
                         pdx pnode nl
114
      return new_nl
115

    
116
-- | Remove an instance and return the new node and instance maps.
117
removeInstance :: NodeList -> Instance.Instance -> NodeList
118
removeInstance nl idata =
119
  let pnode = Instance.pnode idata
120
      snode = Instance.snode idata
121
      pn = Container.find pnode nl
122
      sn = Container.find snode nl
123
      new_nl = Container.addTwo
124
               pnode (Node.removePri pn idata)
125
               snode (Node.removeSec sn idata) nl in
126
  new_nl
127

    
128
-- | Remove an instance and return the new node map.
129
removeInstances :: NodeList -> [Instance.Instance] -> NodeList
130
removeInstances = foldl' removeInstance
131

    
132
-- | Compute the total free disk and memory in the cluster.
133
totalResources :: Container.Container Node.Node -> (Int, Int)
134
totalResources nl =
135
    foldl'
136
    (\ (mem, dsk) node -> (mem + (Node.f_mem node),
137
                           dsk + (Node.f_dsk node)))
138
    (0, 0) (Container.elems nl)
139

    
140
{- | Compute a new version of a cluster given a solution.
141

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

    
145
It first removes the relocated instances after which it places them on
146
their new nodes.
147

    
148
 -}
149
applySolution :: NodeList -> InstanceList -> [Placement] -> NodeList
150
applySolution nl il sol =
151
    let odxes = map (\ (a, b, c, _) -> (Container.find a il,
152
                                        Node.idx (Container.find b nl),
153
                                        Node.idx (Container.find c nl))
154
                    ) sol
155
        idxes = (\ (x, _, _) -> x) (unzip3 odxes)
156
        nc = removeInstances nl idxes
157
    in
158
      foldl' (\ nz (a, b, c) ->
159
                 let new_p = Container.find b nz
160
                     new_s = Container.find c nz in
161
                 fromJust (addInstance nz a new_p new_s)
162
           ) nc odxes
163

    
164

    
165
-- First phase functions
166

    
167
{- | Given a list 1,2,3..n build a list of pairs [(1, [2..n]), (2,
168
    [3..n]), ...]
169

    
170
-}
171
genParts :: [a] -> Int -> [(a, [a])]
172
genParts l count =
173
    case l of
174
      [] -> []
175
      x:xs ->
176
          if length l < count then
177
              []
178
          else
179
              (x, xs) : (genParts xs count)
180

    
181
-- | Generates combinations of count items from the names list.
182
genNames :: Int -> [b] -> [[b]]
183
genNames count1 names1 =
184
  let aux_fn count names current =
185
          case count of
186
            0 -> [current]
187
            _ ->
188
                concatMap
189
                (\ (x, xs) -> aux_fn (count - 1) xs (x:current))
190
                (genParts names count)
191
  in
192
    aux_fn count1 names1 []
193

    
194
{- | Computes the pair of bad nodes and instances.
195

    
196
The bad node list is computed via a simple 'verifyN1' check, and the
197
bad instance list is the list of primary and secondary instances of
198
those nodes.
199

    
200
-}
201
computeBadItems :: NodeList -> InstanceList ->
202
                   ([Node.Node], [Instance.Instance])
203
computeBadItems nl il =
204
  let bad_nodes = verifyN1 $ Container.elems nl
205
      bad_instances = map (\idx -> Container.find idx il) $
206
                      sort $ nub $ concat $
207
                      map (\ n -> (Node.slist n) ++ (Node.plist n)) bad_nodes
208
  in
209
    (bad_nodes, bad_instances)
210

    
211

    
212
{- | Checks if removal of instances results in N+1 pass.
213

    
214
Note: the check removal cannot optimize by scanning only the affected
215
nodes, since the cluster is known to be not healthy; only the check
216
placement can make this shortcut.
217

    
218
-}
219
checkRemoval :: NodeList -> [Instance.Instance] -> Maybe Removal
220
checkRemoval nl victims =
221
  let nx = removeInstances nl victims
222
      failN1 = verifyN1Check (Container.elems nx)
223
  in
224
    if failN1 then
225
      Nothing
226
    else
227
      Just $ Removal nx victims
228

    
229

    
230
-- | Computes the removals list for a given depth
231
computeRemovals :: NodeList
232
                 -> [Instance.Instance]
233
                 -> Int
234
                 -> [Maybe Removal]
235
computeRemovals nl bad_instances depth =
236
    map (checkRemoval nl) $ genNames depth bad_instances
237

    
238
-- Second phase functions
239

    
240
-- | Single-node relocation cost
241
nodeDelta :: Int -> Int -> Int -> Int
242
nodeDelta i p s =
243
    if i == p || i == s then
244
        0
245
    else
246
        1
247

    
248
{-| Compute best solution.
249

    
250
    This function compares two solutions, choosing the minimum valid
251
    solution.
252
-}
253
compareSolutions :: Maybe Solution -> Maybe Solution -> Maybe Solution
254
compareSolutions a b = case (a, b) of
255
  (Nothing, x) -> x
256
  (x, Nothing) -> x
257
  (x, y) -> min x y
258

    
259
-- | Compute best table. Note that the ordering of the arguments is important.
260
compareTables :: Table -> Table -> Table
261
compareTables a@(Table _ _ a_cv _) b@(Table _ _ b_cv _ ) =
262
    if a_cv > b_cv then b else a
263

    
264
-- | Check if a given delta is worse then an existing solution.
265
tooHighDelta :: Maybe Solution -> Int -> Int -> Bool
266
tooHighDelta sol new_delta max_delta =
267
    if new_delta > max_delta && max_delta >=0 then
268
        True
269
    else
270
        case sol of
271
          Nothing -> False
272
          Just (Solution old_delta _) -> old_delta <= new_delta
273

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

    
276
    This is the workhorse of the allocation algorithm: given the
277
    current node and instance maps, the list of instances to be
278
    placed, and the current solution, this will return all possible
279
    solution by recursing until all target instances are placed.
280

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

    
334
-- | Apply a move
335
applyMove :: NodeList -> Instance.Instance
336
          -> IMove -> (Maybe NodeList, Instance.Instance, Int, Int)
337
-- Failover (f)
338
applyMove nl inst Failover =
339
    let old_pdx = Instance.pnode inst
340
        old_sdx = Instance.snode inst
341
        old_p = Container.find old_pdx nl
342
        old_s = Container.find old_sdx nl
343
        int_p = Node.removePri old_p inst
344
        int_s = Node.removeSec old_s inst
345
        new_p = Node.addPri int_s inst
346
        new_s = Node.addSec int_p inst old_sdx
347
        new_nl = if isNothing(new_p) || isNothing(new_s) then Nothing
348
                 else Just $ Container.addTwo old_pdx (fromJust new_s)
349
                      old_sdx (fromJust new_p) nl
350
    in (new_nl, Instance.setBoth inst old_sdx old_pdx, old_sdx, old_pdx)
351

    
352
-- Replace the primary (f:, r:np, f)
353
applyMove nl inst (ReplacePrimary new_pdx) =
354
    let old_pdx = Instance.pnode inst
355
        old_sdx = Instance.snode inst
356
        old_p = Container.find old_pdx nl
357
        old_s = Container.find old_sdx nl
358
        tgt_n = Container.find new_pdx nl
359
        int_p = Node.removePri old_p inst
360
        int_s = Node.removeSec old_s inst
361
        new_p = Node.addPri tgt_n inst
362
        new_s = Node.addSec int_s inst new_pdx
363
        new_nl = if isNothing(new_p) || isNothing(new_s) then Nothing
364
                 else Just $ Container.add new_pdx (fromJust new_p) $
365
                      Container.addTwo old_pdx int_p
366
                               old_sdx (fromJust new_s) nl
367
    in (new_nl, Instance.setPri inst new_pdx, new_pdx, old_sdx)
368

    
369
-- Replace the secondary (r:ns)
370
applyMove nl inst (ReplaceSecondary new_sdx) =
371
    let old_pdx = Instance.pnode inst
372
        old_sdx = Instance.snode inst
373
        old_s = Container.find old_sdx nl
374
        tgt_n = Container.find new_sdx nl
375
        int_s = Node.removeSec old_s inst
376
        new_s = Node.addSec tgt_n inst old_pdx
377
        new_nl = if isNothing(new_s) then Nothing
378
                 else Just $ Container.addTwo new_sdx (fromJust new_s)
379
                      old_sdx int_s nl
380
    in (new_nl, Instance.setSec inst new_sdx, old_pdx, new_sdx)
381

    
382
-- Replace the secondary and failover (r:np, f)
383
applyMove nl inst (ReplaceAndFailover new_pdx) =
384
    let old_pdx = Instance.pnode inst
385
        old_sdx = Instance.snode inst
386
        old_p = Container.find old_pdx nl
387
        old_s = Container.find old_sdx nl
388
        tgt_n = Container.find new_pdx nl
389
        int_p = Node.removePri old_p inst
390
        int_s = Node.removeSec old_s inst
391
        new_p = Node.addPri tgt_n inst
392
        new_s = Node.addSec int_p inst new_pdx
393
        new_nl = if isNothing(new_p) || isNothing(new_s) then Nothing
394
                 else Just $ Container.add new_pdx (fromJust new_p) $
395
                      Container.addTwo old_pdx (fromJust new_s)
396
                               old_sdx int_s nl
397
    in (new_nl, Instance.setBoth inst new_pdx old_pdx, new_pdx, old_pdx)
398

    
399
-- Failver and replace the secondary (f, r:ns)
400
applyMove nl inst (FailoverAndReplace new_sdx) =
401
    let old_pdx = Instance.pnode inst
402
        old_sdx = Instance.snode inst
403
        old_p = Container.find old_pdx nl
404
        old_s = Container.find old_sdx nl
405
        tgt_n = Container.find new_sdx nl
406
        int_p = Node.removePri old_p inst
407
        int_s = Node.removeSec old_s inst
408
        new_p = Node.addPri int_s inst
409
        new_s = Node.addSec tgt_n inst old_sdx
410
        new_nl = if isNothing(new_p) || isNothing(new_s) then Nothing
411
                 else Just $ Container.add new_sdx (fromJust new_s) $
412
                      Container.addTwo old_sdx (fromJust new_p)
413
                               old_pdx int_p nl
414
    in (new_nl, Instance.setBoth inst old_sdx new_sdx, old_sdx, new_sdx)
415

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

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

    
447
possibleMoves False tdx =
448
    [ReplaceSecondary tdx,
449
     ReplaceAndFailover tdx]
450

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

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

    
490
{- | Auxiliary function for solution computation.
491

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

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

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

    
522
{- | Computes the solution at the given depth.
523

    
524
This is a wrapper over both computeRemovals and
525
solutionFromRemovals. In case we have no solution, we return Nothing.
526

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

    
542
-- Solution display functions (pure)
543

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

    
582
                else {- Nothing in common -}
583
                    (printf "r:%s f r:%s" c d,
584
                     [printf "replace-disks -n %s %s" c i,
585
                      printf "migrate %s" i,
586
                      printf "replace-disks -n %s %s" d i])
587

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

    
616
formatCmds :: [[String]] -> String
617
formatCmds cmd_strs =
618
    unlines $ map ("  echo " ++) $
619
    concat $ map (\(a, b) ->
620
        (printf "step %d" (a::Int)):(map ("gnt-instance " ++) b)) $
621
        zip [1..] cmd_strs
622

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

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

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

    
673
-- | Compute the 'total' variance.
674
compCV :: NodeList -> Double
675
compCV nl =
676
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score) = compDetailedCV nl
677
    in mem_cv + dsk_cv + n1_score + res_cv + off_score
678

    
679
printStats :: NodeList -> String
680
printStats nl =
681
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score) = compDetailedCV nl
682
    in printf "f_mem=%.8f, r_mem=%.8f, f_dsk=%.8f, n1=%.3f, uf=%.3f"
683
       mem_cv res_cv dsk_cv n1_score off_score
684

    
685
-- Balancing functions
686

    
687
-- Loading functions
688

    
689
{- | Convert newline and delimiter-separated text.
690

    
691
This function converts a text in tabular format as generated by
692
@gnt-instance list@ and @gnt-node list@ to a list of objects using a
693
supplied conversion function.
694

    
695
-}
696
loadTabular :: String -> ([String] -> (String, a))
697
            -> (a -> Int -> a) -> ([(String, Int)], [(Int, a)])
698
loadTabular text_data convert_fn set_fn =
699
    let lines_data = lines text_data
700
        rows = map (sepSplit '|') lines_data
701
        kerows = (map convert_fn rows)
702
        idxrows = map (\ (idx, (k, v)) -> ((k, idx), (idx, set_fn v idx)))
703
                  (zip [0..] kerows)
704
    in unzip idxrows
705

    
706
-- | For each instance, add its index to its primary and secondary nodes
707
fixNodes :: [(Int, Node.Node)]
708
         -> [(Int, Instance.Instance)]
709
         -> [(Int, Node.Node)]
710
fixNodes nl il =
711
    foldl' (\accu (idx, inst) ->
712
                let
713
                    assocEqual = (\ (i, _) (j, _) -> i == j)
714
                    pdx = Instance.pnode inst
715
                    sdx = Instance.snode inst
716
                    pold = fromJust $ lookup pdx accu
717
                    sold = fromJust $ lookup sdx accu
718
                    pnew = Node.setPri pold idx
719
                    snew = Node.setSec sold idx
720
                    ac1 = deleteBy assocEqual (pdx, pold) accu
721
                    ac2 = deleteBy assocEqual (sdx, sold) ac1
722
                    ac3 = (pdx, pnew):(sdx, snew):ac2
723
                in ac3) nl il
724

    
725
-- | Compute the longest common suffix of a NameList list that
726
-- | starts with a dot
727
longestDomain :: NameList -> String
728
longestDomain [] = ""
729
longestDomain ((_,x):xs) =
730
    let
731
        onlyStrings = snd $ unzip xs
732
    in
733
      foldr (\ suffix accu -> if all (isSuffixOf suffix) onlyStrings
734
                              then suffix
735
                              else accu)
736
      "" $ filter (isPrefixOf ".") (tails x)
737

    
738
-- | Remove tails from the (Int, String) lists
739
stripSuffix :: String -> NameList -> NameList
740
stripSuffix suffix lst =
741
    let sflen = length suffix in
742
    map (\ (key, name) -> (key, take ((length name) - sflen) name)) lst
743

    
744
{-| Initializer function that loads the data from a node and list file
745
    and massages it into the correct format. -}
746
loadData :: String -- ^ Node data in text format
747
         -> String -- ^ Instance data in text format
748
         -> (Container.Container Node.Node,
749
             Container.Container Instance.Instance,
750
             String, NameList, NameList)
751
loadData ndata idata =
752
    let
753
    {- node file: name mem disk -}
754
        (ktn, nl) = loadTabular ndata
755
                    (\ (i:jt:jf:kt:kf:[]) -> (i, Node.create jt jf kt kf))
756
                    Node.setIdx
757
    {- instance file: name mem disk pnode snode -}
758
        (kti, il) = loadTabular idata
759
                    (\ (i:j:k:l:m:[]) -> (i,
760
                                           Instance.create j k
761
                                               (fromJust $ lookup l ktn)
762
                                               (fromJust $ lookup m ktn)))
763
                    Instance.setIdx
764
        nl2 = fixNodes nl il
765
        il3 = Container.fromAssocList il
766
        nl3 = Container.fromAssocList
767
             (map (\ (k, v) -> (k, Node.buildPeers v il3 (length nl2))) nl2)
768
        xtn = swapPairs ktn
769
        xti = swapPairs kti
770
        common_suffix = longestDomain (xti ++ xtn)
771
        stn = stripSuffix common_suffix xtn
772
        sti = stripSuffix common_suffix xti
773
    in
774
      (nl3, il3, common_suffix, stn, sti)