Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Cluster.hs @ 685935f7

History | View | Annotate | Download (22.8 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
    , checkMove
49
    , compCV
50
    , printStats
51
    -- * IAllocator functions
52
    , tryAlloc
53
    , tryReloc
54
    ) where
55

    
56
import Data.List
57
import Text.Printf (printf)
58
import Data.Function
59
import Control.Monad
60

    
61
import qualified Ganeti.HTools.Container as Container
62
import qualified Ganeti.HTools.Instance as Instance
63
import qualified Ganeti.HTools.Node as Node
64
import Ganeti.HTools.Types
65
import Ganeti.HTools.Utils
66

    
67
-- * Types
68

    
69
-- | A separate name for the cluster score type.
70
type Score = Double
71

    
72
-- | The description of an instance placement.
73
type Placement = (Idx, Ndx, Ndx, Score)
74

    
75
-- | Allocation\/relocation solution.
76
type AllocSolution = [OpResult (Node.List, Instance.Instance, [Node.Node])]
77

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

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

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

    
110
-- * Utility functions
111

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

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

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

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

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

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

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

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

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

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

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

    
235
-- * hbal functions
236

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

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

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

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

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

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

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

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

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

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

    
390
possibleMoves False tdx =
391
    [ReplaceSecondary tdx,
392
     ReplaceAndFailover tdx]
393

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

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

    
435
-- * Alocation functions
436

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

    
451
tryAlloc nl _ inst 1 =
452
    let all_nodes = getOnline nl
453
        sols = map (allocateOnSingle nl inst) all_nodes
454
    in return sols
455

    
456
tryAlloc _ _ _ reqn = fail $ "Unsupported number of alllocation \
457
                             \destinations required (" ++ show reqn ++
458
                                               "), only two supported"
459

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

    
480
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
481
                                \destinations required (" ++ show reqn ++
482
                                                  "), only one supported"
483

    
484
-- * Formatting functions
485

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

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

    
549
-- | Given a list of commands, prefix them with @gnt-instance@ and
550
-- also beautify the display a little.
551
formatCmds :: [[String]] -> String
552
formatCmds =
553
    unlines .
554
    concatMap (\(a, b) ->
555
               printf "echo step %d" (a::Int):
556
               printf "check":
557
               map ("gnt-instance " ++) b
558
              ) .
559
    zip [1..]
560

    
561
-- | Converts a solution to string format.
562
printSolution :: Node.List
563
              -> Instance.List
564
              -> [Placement]
565
              -> ([String], [[String]])
566
printSolution nl il sol =
567
    let
568
        nmlen = Container.maxNameLen nl
569
        imlen = Container.maxNameLen il
570
    in
571
      unzip $ zipWith (printSolutionLine nl il nmlen imlen) sol [1..]
572

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

    
588
-- | Shows statistics for a given node list.
589
printStats :: Node.List -> String
590
printStats nl =
591
    let (mem_cv, dsk_cv, n1_score, res_cv, off_score, cpu_cv) =
592
            compDetailedCV nl
593
    in printf "f_mem=%.8f, r_mem=%.8f, f_dsk=%.8f, n1=%.3f, \
594
              \uf=%.3f, r_cpu=%.3f"
595
       mem_cv res_cv dsk_cv n1_score off_score cpu_cv