Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 8880d889

History | View | Annotate | Download (23 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
    , Score
36
    , IMove(..)
37
    , CStats(..)
38
    -- * Generic functions
39
    , totalResources
40
    -- * First phase functions
41
    , computeBadItems
42
    -- * Second phase functions
43
    , printSolution
44
    , printSolutionLine
45
    , formatCmds
46
    , printNodes
47
    -- * Balacing functions
48
    , applyMove
49
    , checkMove
50
    , compCV
51
    , printStats
52
    -- * IAllocator functions
53
    , allocateOnSingle
54
    , allocateOnPair
55
    , tryAlloc
56
    , tryReloc
57
    ) where
58

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

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

    
70
-- * Types
71

    
72
-- | A separate name for the cluster score type.
73
type Score = Double
74

    
75
-- | The description of an instance placement.
76
type Placement = (Idx, Ndx, Ndx, Score)
77

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

    
81
-- | An instance move definition
82
data IMove = Failover                -- ^ Failover the instance (f)
83
           | ReplacePrimary Ndx      -- ^ Replace primary (f, r:np, f)
84
           | ReplaceSecondary Ndx    -- ^ Replace secondary (r:ns)
85
           | ReplaceAndFailover Ndx  -- ^ Replace secondary, failover (r:np, f)
86
           | FailoverAndReplace Ndx  -- ^ Failover, replace secondary (f, r:ns)
87
             deriving (Show)
88

    
89
-- | The complete state for the balancing solution
90
data Table = Table Node.List Instance.List Score [Placement]
91
             deriving (Show)
92

    
93
data CStats = CStats { cs_fmem :: Int    -- ^ Cluster free mem
94
                     , cs_fdsk :: Int    -- ^ Cluster free disk
95
                     , cs_amem :: Int    -- ^ Cluster allocatable mem
96
                     , cs_adsk :: Int    -- ^ Cluster allocatable disk
97
                     , cs_acpu :: Int    -- ^ Cluster allocatable cpus
98
                     , cs_mmem :: Int    -- ^ Max node allocatable mem
99
                     , cs_mdsk :: Int    -- ^ Max node allocatable disk
100
                     , cs_mcpu :: Int    -- ^ Max node allocatable cpu
101
                     , cs_imem :: Int    -- ^ Instance used mem
102
                     , cs_idsk :: Int    -- ^ Instance used disk
103
                     , cs_icpu :: Int    -- ^ Instance used cpu
104
                     , cs_tmem :: Double -- ^ Cluster total mem
105
                     , cs_tdsk :: Double -- ^ Cluster total disk
106
                     , cs_tcpu :: Double -- ^ Cluster total cpus
107
                     , cs_xmem :: Int    -- ^ Unnacounted for mem
108
                     , cs_nmem :: Int    -- ^ Node own memory
109
                     , cs_score :: Score -- ^ The cluster score
110
                     , cs_ninst :: Int   -- ^ The total number of instances
111
                     }
112

    
113
-- * Utility functions
114

    
115
-- | Verifies the N+1 status and return the affected nodes.
116
verifyN1 :: [Node.Node] -> [Node.Node]
117
verifyN1 = filter Node.failN1
118

    
119
{-| Computes the pair of bad nodes and instances.
120

    
121
The bad node list is computed via a simple 'verifyN1' check, and the
122
bad instance list is the list of primary and secondary instances of
123
those nodes.
124

    
125
-}
126
computeBadItems :: Node.List -> Instance.List ->
127
                   ([Node.Node], [Instance.Instance])
128
computeBadItems nl il =
129
  let bad_nodes = verifyN1 $ getOnline nl
130
      bad_instances = map (\idx -> Container.find idx il) .
131
                      sort . nub $
132
                      concatMap (\ n -> Node.slist n ++ Node.plist n) bad_nodes
133
  in
134
    (bad_nodes, bad_instances)
135

    
136
emptyCStats :: CStats
137
emptyCStats = CStats { cs_fmem = 0
138
                     , cs_fdsk = 0
139
                     , cs_amem = 0
140
                     , cs_adsk = 0
141
                     , cs_acpu = 0
142
                     , cs_mmem = 0
143
                     , cs_mdsk = 0
144
                     , cs_mcpu = 0
145
                     , cs_imem = 0
146
                     , cs_idsk = 0
147
                     , cs_icpu = 0
148
                     , cs_tmem = 0
149
                     , cs_tdsk = 0
150
                     , cs_tcpu = 0
151
                     , cs_xmem = 0
152
                     , cs_nmem = 0
153
                     , cs_score = 0
154
                     , cs_ninst = 0
155
                     }
156

    
157
updateCStats :: CStats -> Node.Node -> CStats
158
updateCStats cs node =
159
    let CStats { cs_fmem = x_fmem, cs_fdsk = x_fdsk,
160
                 cs_amem = x_amem, cs_acpu = x_acpu, cs_adsk = x_adsk,
161
                 cs_mmem = x_mmem, cs_mdsk = x_mdsk, cs_mcpu = x_mcpu,
162
                 cs_imem = x_imem, cs_idsk = x_idsk, cs_icpu = x_icpu,
163
                 cs_tmem = x_tmem, cs_tdsk = x_tdsk, cs_tcpu = x_tcpu,
164
                 cs_xmem = x_xmem, cs_nmem = x_nmem, cs_ninst = x_ninst
165
               }
166
            = cs
167
        inc_amem = Node.f_mem node - Node.r_mem node
168
        inc_amem' = if inc_amem > 0 then inc_amem else 0
169
        inc_adsk = Node.availDisk node
170
        inc_imem = truncate (Node.t_mem node) - Node.n_mem node
171
                   - Node.x_mem node - Node.f_mem node
172
        inc_icpu = Node.u_cpu node
173
        inc_idsk = truncate (Node.t_dsk node) - Node.f_dsk node
174

    
175
    in cs { cs_fmem = x_fmem + Node.f_mem node
176
          , cs_fdsk = x_fdsk + Node.f_dsk node
177
          , cs_amem = x_amem + inc_amem'
178
          , cs_adsk = x_adsk + inc_adsk
179
          , cs_acpu = x_acpu
180
          , cs_mmem = max x_mmem inc_amem'
181
          , cs_mdsk = max x_mdsk inc_adsk
182
          , cs_mcpu = x_mcpu
183
          , cs_imem = x_imem + inc_imem
184
          , cs_idsk = x_idsk + inc_idsk
185
          , cs_icpu = x_icpu + inc_icpu
186
          , cs_tmem = x_tmem + Node.t_mem node
187
          , cs_tdsk = x_tdsk + Node.t_dsk node
188
          , cs_tcpu = x_tcpu + Node.t_cpu node
189
          , cs_xmem = x_xmem + Node.x_mem node
190
          , cs_nmem = x_nmem + Node.n_mem node
191
          , cs_ninst = x_ninst + length (Node.plist node)
192
          }
193

    
194
-- | Compute the total free disk and memory in the cluster.
195
totalResources :: Node.List -> CStats
196
totalResources nl =
197
    let cs = foldl' updateCStats emptyCStats . Container.elems $ nl
198
    in cs { cs_score = compCV nl }
199

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

    
227
-- | Compute the /total/ variance.
228
compCV :: Node.List -> Double
229
compCV nl =
230
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv) =
231
            compDetailedCV nl
232
    in mem_cv + dsk_cv + n1_score + res_cv + off_score + cpu_cv
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 (Node.List, Instance.Instance)
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)
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 (Node.List, Instance.Instance)
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
    in new_nl
358

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

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

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

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

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

    
437
-- * Alocation functions
438

    
439
-- | Try to allocate an instance on the cluster.
440
tryAlloc :: (Monad m) =>
441
            Node.List         -- ^ The node list
442
         -> Instance.List     -- ^ The instance list
443
         -> Instance.Instance -- ^ The instance to allocate
444
         -> Int               -- ^ Required number of nodes
445
         -> m AllocSolution   -- ^ Possible solution list
446
tryAlloc nl _ inst 2 =
447
    let all_nodes = getOnline nl
448
        all_pairs = liftM2 (,) all_nodes all_nodes
449
        ok_pairs = filter (\(x, y) -> Node.idx x /= Node.idx y) all_pairs
450
        sols = map (\(p, s) -> do
451
                      (mnl, i) <- allocateOnPair nl inst p s
452
                      return (mnl, i, [p, s]))
453
               ok_pairs
454
    in return sols
455

    
456
tryAlloc nl _ inst 1 =
457
    let all_nodes = getOnline nl
458
        sols = map (\p -> do
459
                      (mnl, i) <- allocateOnSingle nl inst p
460
                      return (mnl, i, [p]))
461
               all_nodes
462
    in return sols
463

    
464
tryAlloc _ _ _ reqn = fail $ "Unsupported number of alllocation \
465
                             \destinations required (" ++ show reqn ++
466
                                               "), only two supported"
467

    
468
-- | Try to allocate an instance on the cluster.
469
tryReloc :: (Monad m) =>
470
            Node.List       -- ^ The node list
471
         -> Instance.List   -- ^ The instance list
472
         -> Idx             -- ^ The index of the instance to move
473
         -> Int             -- ^ The numver of nodes required
474
         -> [Ndx]           -- ^ Nodes which should not be used
475
         -> m AllocSolution -- ^ Solution list
476
tryReloc nl il xid 1 ex_idx =
477
    let all_nodes = getOnline nl
478
        inst = Container.find xid il
479
        ex_idx' = Instance.pnode inst:ex_idx
480
        valid_nodes = filter (not . flip elem ex_idx' . Node.idx) all_nodes
481
        valid_idxes = map Node.idx valid_nodes
482
        sols1 = map (\x -> do
483
                       (mnl, i, _, _) <- applyMove nl inst (ReplaceSecondary x)
484
                       return (mnl, i, [Container.find x nl])
485
                     ) valid_idxes
486
    in return sols1
487

    
488
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
489
                                \destinations required (" ++ show reqn ++
490
                                                  "), only one supported"
491

    
492
-- * Formatting functions
493

    
494
-- | Given the original and final nodes, computes the relocation description.
495
computeMoves :: String -- ^ The instance name
496
             -> String -- ^ Original primary
497
             -> String -- ^ Original secondary
498
             -> String -- ^ New primary
499
             -> String -- ^ New secondary
500
             -> (String, [String])
501
                -- ^ Tuple of moves and commands list; moves is containing
502
                -- either @/f/@ for failover or @/r:name/@ for replace
503
                -- secondary, while the command list holds gnt-instance
504
                -- commands (without that prefix), e.g \"@failover instance1@\"
505
computeMoves i a b c d
506
    -- same primary
507
    | c == a =
508
        if d == b
509
        then {- Same sec??! -} ("-", [])
510
        else {- Change of secondary -}
511
            (printf "r:%s" d, [rep d])
512
    -- failover and ...
513
    | c == b =
514
        if d == a
515
        then {- that's all -} ("f", [mig])
516
        else (printf "f r:%s" d, [mig, rep d])
517
    -- ... and keep primary as secondary
518
    | d == a =
519
        (printf "r:%s f" c, [rep c, mig])
520
    -- ... keep same secondary
521
    | d == b =
522
        (printf "f r:%s f" c, [mig, rep c, mig])
523
    -- nothing in common -
524
    | otherwise =
525
        (printf "r:%s f r:%s" c d, [rep c, mig, rep d])
526
    where mig = printf "migrate -f %s" i::String
527
          rep n = printf "replace-disks -n %s %s" n i
528

    
529
-- | Converts a placement to string format.
530
printSolutionLine :: Node.List     -- ^ The node list
531
                  -> Instance.List -- ^ The instance list
532
                  -> Int           -- ^ Maximum node name length
533
                  -> Int           -- ^ Maximum instance name length
534
                  -> Placement     -- ^ The current placement
535
                  -> Int           -- ^ The index of the placement in
536
                                   -- the solution
537
                  -> (String, [String])
538
printSolutionLine nl il nmlen imlen plc pos =
539
    let
540
        pmlen = (2*nmlen + 1)
541
        (i, p, s, c) = plc
542
        inst = Container.find i il
543
        inam = Instance.name inst
544
        npri = Container.nameOf nl p
545
        nsec = Container.nameOf nl s
546
        opri = Container.nameOf nl $ Instance.pnode inst
547
        osec = Container.nameOf nl $ Instance.snode inst
548
        (moves, cmds) =  computeMoves inam opri osec npri nsec
549
        ostr = printf "%s:%s" opri osec::String
550
        nstr = printf "%s:%s" npri nsec::String
551
    in
552
      (printf "  %3d. %-*s %-*s => %-*s %.8f a=%s"
553
       pos imlen inam pmlen ostr
554
       pmlen nstr c moves,
555
       cmds)
556

    
557
-- | Given a list of commands, prefix them with @gnt-instance@ and
558
-- also beautify the display a little.
559
formatCmds :: [[String]] -> String
560
formatCmds =
561
    unlines .
562
    concatMap (\(a, b) ->
563
               printf "echo step %d" (a::Int):
564
               printf "check":
565
               map ("gnt-instance " ++) b
566
              ) .
567
    zip [1..]
568

    
569
-- | Converts a solution to string format.
570
printSolution :: Node.List
571
              -> Instance.List
572
              -> [Placement]
573
              -> ([String], [[String]])
574
printSolution nl il sol =
575
    let
576
        nmlen = Container.maxNameLen nl
577
        imlen = Container.maxNameLen il
578
    in
579
      unzip $ zipWith (printSolutionLine nl il nmlen imlen) sol [1..]
580

    
581
-- | Print the node list.
582
printNodes :: Node.List -> String
583
printNodes nl =
584
    let snl = sortBy (compare `on` Node.idx) (Container.elems nl)
585
        m_name = maximum . map (length . Node.name) $ snl
586
        helper = Node.list m_name
587
        header = printf
588
                 "%2s %-*s %5s %5s %5s %5s %5s %5s %5s %5s %4s %4s \
589
                 \%3s %3s %6s %6s %5s"
590
                 " F" m_name "Name"
591
                 "t_mem" "n_mem" "i_mem" "x_mem" "f_mem" "r_mem"
592
                 "t_dsk" "f_dsk" "pcpu" "vcpu"
593
                 "pri" "sec" "p_fmem" "p_fdsk" "r_cpu"::String
594
    in unlines (header:map helper snl)
595

    
596
-- | Shows statistics for a given node list.
597
printStats :: Node.List -> String
598
printStats nl =
599
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv) =
600
            compDetailedCV nl
601
    in printf "f_mem=%.8f, r_mem=%.8f, f_dsk=%.8f, n1=%.3f, \
602
              \uf=%.3f, r_cpu=%.3f"
603
       mem_cv res_cv dsk_cv n1_score off_score cpu_cv