Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 8c4c6a8a

History | View | Annotate | Download (22.3 kB)

1
{-| Implementation of cluster-wide logic.
2

    
3
This module holds all pure cluster-logic; I\/O related functionality
4
goes into the "Main" module for the individual binaries.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2009 Google Inc.
11

    
12
This program is free software; you can redistribute it and/or modify
13
it under the terms of the GNU General Public License as published by
14
the Free Software Foundation; either version 2 of the License, or
15
(at your option) any later version.
16

    
17
This program is distributed in the hope that it will be useful, but
18
WITHOUT ANY WARRANTY; without even the implied warranty of
19
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20
General Public License for more details.
21

    
22
You should have received a copy of the GNU General Public License
23
along with this program; if not, write to the Free Software
24
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25
02110-1301, USA.
26

    
27
-}
28

    
29
module Ganeti.HTools.Cluster
30
    (
31
     -- * Types
32
      Placement
33
    , AllocSolution
34
    , Table(..)
35
    , 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
                     }
110

    
111
-- * Utility functions
112

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

    
117
{-| Computes the pair of bad nodes and instances.
118

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

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

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

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

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

    
189
-- | Compute the total free disk and memory in the cluster.
190
totalResources :: Node.List -> CStats
191
totalResources = foldl' updateCStats emptyCStats . Container.elems
192

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

    
220
-- | Compute the /total/ variance.
221
compCV :: Node.List -> Double
222
compCV nl =
223
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv) =
224
            compDetailedCV nl
225
    in mem_cv + dsk_cv + n1_score + res_cv + off_score + cpu_cv
226

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

    
231
-- * hbal functions
232

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

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

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

    
275
-- Replace the secondary (r:ns)
276
applyMove nl inst (ReplaceSecondary new_sdx) =
277
    let old_pdx = Instance.pnode inst
278
        old_sdx = Instance.snode inst
279
        old_s = Container.find old_sdx nl
280
        tgt_n = Container.find new_sdx nl
281
        int_s = Node.removeSec old_s inst
282
        new_nl = Node.addSec tgt_n inst old_pdx >>=
283
                 \new_s -> return $ Container.addTwo new_sdx
284
                           new_s old_sdx int_s nl
285
    in (new_nl, Instance.setSec inst new_sdx, old_pdx, new_sdx)
286

    
287
-- Replace the secondary and failover (r:np, f)
288
applyMove nl inst (ReplaceAndFailover new_pdx) =
289
    let old_pdx = Instance.pnode inst
290
        old_sdx = Instance.snode inst
291
        old_p = Container.find old_pdx nl
292
        old_s = Container.find old_sdx nl
293
        tgt_n = Container.find new_pdx nl
294
        int_p = Node.removePri old_p inst
295
        int_s = Node.removeSec old_s inst
296
        new_nl = do -- Maybe monad
297
          new_p <- Node.addPri tgt_n inst
298
          new_s <- Node.addSec int_p inst new_pdx
299
          return . Container.add new_pdx new_p $
300
                 Container.addTwo old_pdx new_s old_sdx int_s nl
301
    in (new_nl, Instance.setBoth inst new_pdx old_pdx, new_pdx, old_pdx)
302

    
303
-- Failver and replace the secondary (f, r:ns)
304
applyMove nl inst (FailoverAndReplace new_sdx) =
305
    let old_pdx = Instance.pnode inst
306
        old_sdx = Instance.snode inst
307
        old_p = Container.find old_pdx nl
308
        old_s = Container.find old_sdx nl
309
        tgt_n = Container.find new_sdx nl
310
        int_p = Node.removePri old_p inst
311
        int_s = Node.removeSec old_s inst
312
        new_nl = do -- Maybe monad
313
          new_p <- Node.addPri int_s inst
314
          new_s <- Node.addSec tgt_n inst old_sdx
315
          return . Container.add new_sdx new_s $
316
                 Container.addTwo old_sdx new_p old_pdx int_p nl
317
    in (new_nl, Instance.setBoth inst old_sdx new_sdx, old_sdx, new_sdx)
318

    
319
-- | Tries to allocate an instance on one given node.
320
allocateOnSingle :: Node.List -> Instance.Instance -> Node.Node
321
                 -> (OpResult Node.List, Instance.Instance)
322
allocateOnSingle nl inst p =
323
    let new_pdx = Node.idx p
324
        new_nl = Node.addPri p inst >>= \new_p ->
325
                 return $ Container.add new_pdx new_p nl
326
    in (new_nl, Instance.setBoth inst new_pdx Node.noSecondary)
327

    
328
-- | Tries to allocate an instance on a given pair of nodes.
329
allocateOnPair :: Node.List -> Instance.Instance -> Node.Node -> Node.Node
330
               -> (OpResult Node.List, Instance.Instance)
331
allocateOnPair nl inst tgt_p tgt_s =
332
    let new_pdx = Node.idx tgt_p
333
        new_sdx = Node.idx tgt_s
334
        new_nl = do -- Maybe monad
335
          new_p <- Node.addPri tgt_p inst
336
          new_s <- Node.addSec tgt_s inst new_pdx
337
          return $ Container.addTwo new_pdx new_p new_sdx new_s nl
338
    in (new_nl, Instance.setBoth inst new_pdx new_sdx)
339

    
340
-- | Tries to perform an instance move and returns the best table
341
-- between the original one and the new one.
342
checkSingleStep :: Table -- ^ The original table
343
                -> Instance.Instance -- ^ The instance to move
344
                -> Table -- ^ The current best table
345
                -> IMove -- ^ The move to apply
346
                -> Table -- ^ The final best table
347
checkSingleStep ini_tbl target cur_tbl move =
348
    let
349
        Table ini_nl ini_il _ ini_plc = ini_tbl
350
        (tmp_nl, new_inst, pri_idx, sec_idx) = applyMove ini_nl target move
351
    in
352
      case tmp_nl of
353
        OpFail _ -> cur_tbl
354
        OpGood upd_nl ->
355
            let tgt_idx = Instance.idx target
356
                upd_cvar = compCV upd_nl
357
                upd_il = Container.add tgt_idx new_inst ini_il
358
                upd_plc = (tgt_idx, pri_idx, sec_idx, upd_cvar):ini_plc
359
                upd_tbl = Table upd_nl upd_il upd_cvar upd_plc
360
            in
361
              compareTables cur_tbl upd_tbl
362

    
363
-- | Given the status of the current secondary as a valid new node
364
-- and the current candidate target node,
365
-- generate the possible moves for a instance.
366
possibleMoves :: Bool -> Ndx -> [IMove]
367
possibleMoves True tdx =
368
    [ReplaceSecondary tdx,
369
     ReplaceAndFailover tdx,
370
     ReplacePrimary tdx,
371
     FailoverAndReplace tdx]
372

    
373
possibleMoves False tdx =
374
    [ReplaceSecondary tdx,
375
     ReplaceAndFailover tdx]
376

    
377
-- | Compute the best move for a given instance.
378
checkInstanceMove :: [Ndx]             -- Allowed target node indices
379
                  -> Table             -- Original table
380
                  -> Instance.Instance -- Instance to move
381
                  -> Table             -- Best new table for this instance
382
checkInstanceMove nodes_idx ini_tbl target =
383
    let
384
        opdx = Instance.pnode target
385
        osdx = Instance.snode target
386
        nodes = filter (\idx -> idx /= opdx && idx /= osdx) nodes_idx
387
        use_secondary = elem osdx nodes_idx
388
        aft_failover = if use_secondary -- if allowed to failover
389
                       then checkSingleStep ini_tbl target ini_tbl Failover
390
                       else ini_tbl
391
        all_moves = concatMap (possibleMoves use_secondary) nodes
392
    in
393
      -- iterate over the possible nodes for this instance
394
      foldl' (checkSingleStep ini_tbl target) aft_failover all_moves
395

    
396
-- | Compute the best next move.
397
checkMove :: [Ndx]               -- ^ Allowed target node indices
398
          -> Table               -- ^ The current solution
399
          -> [Instance.Instance] -- ^ List of instances still to move
400
          -> Table               -- ^ The new solution
401
checkMove nodes_idx ini_tbl victims =
402
    let Table _ _ _ ini_plc = ini_tbl
403
        -- iterate over all instances, computing the best move
404
        best_tbl =
405
            foldl'
406
            (\ step_tbl elem ->
407
                 if Instance.snode elem == Node.noSecondary then step_tbl
408
                    else compareTables step_tbl $
409
                         checkInstanceMove nodes_idx ini_tbl elem)
410
            ini_tbl victims
411
        Table _ _ _ best_plc = best_tbl
412
    in
413
      if length best_plc == length ini_plc then -- no advancement
414
          ini_tbl
415
      else
416
          best_tbl
417

    
418
-- * Alocation functions
419

    
420
-- | Try to allocate an instance on the cluster.
421
tryAlloc :: (Monad m) =>
422
            Node.List         -- ^ The node list
423
         -> Instance.List     -- ^ The instance list
424
         -> Instance.Instance -- ^ The instance to allocate
425
         -> Int               -- ^ Required number of nodes
426
         -> m AllocSolution   -- ^ Possible solution list
427
tryAlloc nl _ inst 2 =
428
    let all_nodes = getOnline nl
429
        all_pairs = liftM2 (,) all_nodes all_nodes
430
        ok_pairs = filter (\(x, y) -> Node.idx x /= Node.idx y) all_pairs
431
        sols = map (\(p, s) -> let (mnl, i) = allocateOnPair nl inst p s
432
                               in (mnl, i, [p, s]))
433
               ok_pairs
434
    in return sols
435

    
436
tryAlloc nl _ inst 1 =
437
    let all_nodes = getOnline nl
438
        sols = map (\p -> let (mnl, i) = allocateOnSingle nl inst p
439
                          in (mnl, i, [p]))
440
               all_nodes
441
    in return sols
442

    
443
tryAlloc _ _ _ reqn = fail $ "Unsupported number of alllocation \
444
                             \destinations required (" ++ show reqn ++
445
                                               "), only two supported"
446

    
447
-- | Try to allocate an instance on the cluster.
448
tryReloc :: (Monad m) =>
449
            Node.List       -- ^ The node list
450
         -> Instance.List   -- ^ The instance list
451
         -> Idx             -- ^ The index of the instance to move
452
         -> Int             -- ^ The numver of nodes required
453
         -> [Ndx]           -- ^ Nodes which should not be used
454
         -> m AllocSolution -- ^ Solution list
455
tryReloc nl il xid 1 ex_idx =
456
    let all_nodes = getOnline nl
457
        inst = Container.find xid il
458
        ex_idx' = Instance.pnode inst:ex_idx
459
        valid_nodes = filter (not . flip elem ex_idx' . Node.idx) all_nodes
460
        valid_idxes = map Node.idx valid_nodes
461
        sols1 = map (\x -> let (mnl, i, _, _) =
462
                                   applyMove nl inst (ReplaceSecondary x)
463
                           in (mnl, i, [Container.find x nl])
464
                     ) valid_idxes
465
    in return sols1
466

    
467
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
468
                                \destinations required (" ++ show reqn ++
469
                                                  "), only one supported"
470

    
471
-- * Formatting functions
472

    
473
-- | Given the original and final nodes, computes the relocation description.
474
computeMoves :: String -- ^ The instance name
475
             -> String -- ^ Original primary
476
             -> String -- ^ Original secondary
477
             -> String -- ^ New primary
478
             -> String -- ^ New secondary
479
             -> (String, [String])
480
                -- ^ Tuple of moves and commands list; moves is containing
481
                -- either @/f/@ for failover or @/r:name/@ for replace
482
                -- secondary, while the command list holds gnt-instance
483
                -- commands (without that prefix), e.g \"@failover instance1@\"
484
computeMoves i a b c d
485
    -- same primary
486
    | c == a =
487
        if d == b
488
        then {- Same sec??! -} ("-", [])
489
        else {- Change of secondary -}
490
            (printf "r:%s" d, [rep d])
491
    -- failover and ...
492
    | c == b =
493
        if d == a
494
        then {- that's all -} ("f", [mig])
495
        else (printf "f r:%s" d, [mig, rep d])
496
    -- ... and keep primary as secondary
497
    | d == a =
498
        (printf "r:%s f" c, [rep c, mig])
499
    -- ... keep same secondary
500
    | d == b =
501
        (printf "f r:%s f" c, [mig, rep c, mig])
502
    -- nothing in common -
503
    | otherwise =
504
        (printf "r:%s f r:%s" c d, [rep c, mig, rep d])
505
    where mig = printf "migrate -f %s" i::String
506
          rep n = printf "replace-disks -n %s %s" n i
507

    
508
-- | Converts a placement to string format.
509
printSolutionLine :: Node.List     -- ^ The node list
510
                  -> Instance.List -- ^ The instance list
511
                  -> Int           -- ^ Maximum node name length
512
                  -> Int           -- ^ Maximum instance name length
513
                  -> Placement     -- ^ The current placement
514
                  -> Int           -- ^ The index of the placement in
515
                                   -- the solution
516
                  -> (String, [String])
517
printSolutionLine nl il nmlen imlen plc pos =
518
    let
519
        pmlen = (2*nmlen + 1)
520
        (i, p, s, c) = plc
521
        inst = Container.find i il
522
        inam = Instance.name inst
523
        npri = Container.nameOf nl p
524
        nsec = Container.nameOf nl s
525
        opri = Container.nameOf nl $ Instance.pnode inst
526
        osec = Container.nameOf nl $ Instance.snode inst
527
        (moves, cmds) =  computeMoves inam opri osec npri nsec
528
        ostr = printf "%s:%s" opri osec::String
529
        nstr = printf "%s:%s" npri nsec::String
530
    in
531
      (printf "  %3d. %-*s %-*s => %-*s %.8f a=%s"
532
       pos imlen inam pmlen ostr
533
       pmlen nstr c moves,
534
       cmds)
535

    
536
-- | Given a list of commands, prefix them with @gnt-instance@ and
537
-- also beautify the display a little.
538
formatCmds :: [[String]] -> String
539
formatCmds =
540
    unlines .
541
    concatMap (\(a, b) ->
542
               printf "echo step %d" (a::Int):
543
               printf "check":
544
               map ("gnt-instance " ++) b
545
              ) .
546
    zip [1..]
547

    
548
-- | Converts a solution to string format.
549
printSolution :: Node.List
550
              -> Instance.List
551
              -> [Placement]
552
              -> ([String], [[String]])
553
printSolution nl il sol =
554
    let
555
        nmlen = Container.maxNameLen nl
556
        imlen = Container.maxNameLen il
557
    in
558
      unzip $ zipWith (printSolutionLine nl il nmlen imlen) sol [1..]
559

    
560
-- | Print the node list.
561
printNodes :: Node.List -> String
562
printNodes nl =
563
    let snl = sortBy (compare `on` Node.idx) (Container.elems nl)
564
        m_name = maximum . map (length . Node.name) $ snl
565
        helper = Node.list m_name
566
        header = printf
567
                 "%2s %-*s %5s %5s %5s %5s %5s %5s %5s %5s %4s %4s \
568
                 \%3s %3s %6s %6s %5s"
569
                 " F" m_name "Name"
570
                 "t_mem" "n_mem" "i_mem" "x_mem" "f_mem" "r_mem"
571
                 "t_dsk" "f_dsk" "pcpu" "vcpu"
572
                 "pri" "sec" "p_fmem" "p_fdsk" "r_cpu"::String
573
    in unlines (header:map helper snl)
574

    
575
-- | Shows statistics for a given node list.
576
printStats :: Node.List -> String
577
printStats nl =
578
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv) =
579
            compDetailedCV nl
580
    in printf "f_mem=%.8f, r_mem=%.8f, f_dsk=%.8f, n1=%.3f, \
581
              \uf=%.3f, r_cpu=%.3f"
582
       mem_cv res_cv dsk_cv n1_score off_score cpu_cv