Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Cluster.hs @ e4491427

History | View | Annotate | Download (45.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, 2010, 2011 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
      AllocSolution(..)
33
    , Table(..)
34
    , CStats(..)
35
    , AllocStats
36
    -- * Generic functions
37
    , totalResources
38
    , computeAllocationDelta
39
    -- * First phase functions
40
    , computeBadItems
41
    -- * Second phase functions
42
    , printSolutionLine
43
    , formatCmds
44
    , involvedNodes
45
    , splitJobs
46
    -- * Display functions
47
    , printNodes
48
    , printInsts
49
    -- * Balacing functions
50
    , checkMove
51
    , doNextBalance
52
    , tryBalance
53
    , compCV
54
    , compDetailedCV
55
    , printStats
56
    , iMoveToJob
57
    -- * IAllocator functions
58
    , genAllocNodes
59
    , tryAlloc
60
    , tryMGAlloc
61
    , tryReloc
62
    , tryMGReloc
63
    , tryEvac
64
    , tryMGEvac
65
    , collapseFailures
66
    -- * Allocation functions
67
    , iterateAlloc
68
    , tieredAlloc
69
    , tieredSpecMap
70
     -- * Node group functions
71
    , instanceGroup
72
    , findSplitInstances
73
    , splitCluster
74
    ) where
75

    
76
import Data.Function (on)
77
import Data.List
78
import Data.Ord (comparing)
79
import Text.Printf (printf)
80
import Control.Monad
81
import Control.Parallel.Strategies
82

    
83
import qualified Ganeti.HTools.Container as Container
84
import qualified Ganeti.HTools.Instance as Instance
85
import qualified Ganeti.HTools.Node as Node
86
import qualified Ganeti.HTools.Group as Group
87
import Ganeti.HTools.Types
88
import Ganeti.HTools.Utils
89
import qualified Ganeti.OpCodes as OpCodes
90

    
91
-- * Types
92

    
93
-- | Allocation\/relocation solution.
94
data AllocSolution = AllocSolution
95
  { asFailures  :: [FailMode]          -- ^ Failure counts
96
  , asAllocs    :: Int                 -- ^ Good allocation count
97
  , asSolutions :: [Node.AllocElement] -- ^ The actual result, length
98
                                       -- of the list depends on the
99
                                       -- allocation/relocation mode
100
  , asLog       :: [String]            -- ^ A list of informational messages
101
  }
102

    
103
-- | Allocation results, as used in 'iterateAlloc' and 'tieredAlloc'.
104
type AllocResult = (FailStats, Node.List, Instance.List,
105
                    [Instance.Instance], [CStats])
106

    
107

    
108
-- | A type denoting the valid allocation mode/pairs.
109
-- For a one-node allocation, this will be a @Left ['Node.Node']@,
110
-- whereas for a two-node allocation, this will be a @Right
111
-- [('Node.Node', 'Node.Node')]@.
112
type AllocNodes = Either [Ndx] [(Ndx, Ndx)]
113

    
114
-- | The empty solution we start with when computing allocations
115
emptySolution :: AllocSolution
116
emptySolution = AllocSolution { asFailures = [], asAllocs = 0
117
                              , asSolutions = [], asLog = [] }
118

    
119
-- | The complete state for the balancing solution
120
data Table = Table Node.List Instance.List Score [Placement]
121
             deriving (Show, Read)
122

    
123
data CStats = CStats { csFmem :: Int    -- ^ Cluster free mem
124
                     , csFdsk :: Int    -- ^ Cluster free disk
125
                     , csAmem :: Int    -- ^ Cluster allocatable mem
126
                     , csAdsk :: Int    -- ^ Cluster allocatable disk
127
                     , csAcpu :: Int    -- ^ Cluster allocatable cpus
128
                     , csMmem :: Int    -- ^ Max node allocatable mem
129
                     , csMdsk :: Int    -- ^ Max node allocatable disk
130
                     , csMcpu :: Int    -- ^ Max node allocatable cpu
131
                     , csImem :: Int    -- ^ Instance used mem
132
                     , csIdsk :: Int    -- ^ Instance used disk
133
                     , csIcpu :: Int    -- ^ Instance used cpu
134
                     , csTmem :: Double -- ^ Cluster total mem
135
                     , csTdsk :: Double -- ^ Cluster total disk
136
                     , csTcpu :: Double -- ^ Cluster total cpus
137
                     , csVcpu :: Int    -- ^ Cluster virtual cpus (if
138
                                        -- node pCpu has been set,
139
                                        -- otherwise -1)
140
                     , csXmem :: Int    -- ^ Unnacounted for mem
141
                     , csNmem :: Int    -- ^ Node own memory
142
                     , csScore :: Score -- ^ The cluster score
143
                     , csNinst :: Int   -- ^ The total number of instances
144
                     }
145
            deriving (Show, Read)
146

    
147
-- | Currently used, possibly to allocate, unallocable
148
type AllocStats = (RSpec, RSpec, RSpec)
149

    
150
-- * Utility functions
151

    
152
-- | Verifies the N+1 status and return the affected nodes.
153
verifyN1 :: [Node.Node] -> [Node.Node]
154
verifyN1 = filter Node.failN1
155

    
156
{-| Computes the pair of bad nodes and instances.
157

    
158
The bad node list is computed via a simple 'verifyN1' check, and the
159
bad instance list is the list of primary and secondary instances of
160
those nodes.
161

    
162
-}
163
computeBadItems :: Node.List -> Instance.List ->
164
                   ([Node.Node], [Instance.Instance])
165
computeBadItems nl il =
166
  let bad_nodes = verifyN1 $ getOnline nl
167
      bad_instances = map (`Container.find` il) .
168
                      sort . nub $
169
                      concatMap (\ n -> Node.sList n ++ Node.pList n) bad_nodes
170
  in
171
    (bad_nodes, bad_instances)
172

    
173
-- | Zero-initializer for the CStats type
174
emptyCStats :: CStats
175
emptyCStats = CStats 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
176

    
177
-- | Update stats with data from a new node
178
updateCStats :: CStats -> Node.Node -> CStats
179
updateCStats cs node =
180
    let CStats { csFmem = x_fmem, csFdsk = x_fdsk,
181
                 csAmem = x_amem, csAcpu = x_acpu, csAdsk = x_adsk,
182
                 csMmem = x_mmem, csMdsk = x_mdsk, csMcpu = x_mcpu,
183
                 csImem = x_imem, csIdsk = x_idsk, csIcpu = x_icpu,
184
                 csTmem = x_tmem, csTdsk = x_tdsk, csTcpu = x_tcpu,
185
                 csVcpu = x_vcpu,
186
                 csXmem = x_xmem, csNmem = x_nmem, csNinst = x_ninst
187
               }
188
            = cs
189
        inc_amem = Node.fMem node - Node.rMem node
190
        inc_amem' = if inc_amem > 0 then inc_amem else 0
191
        inc_adsk = Node.availDisk node
192
        inc_imem = truncate (Node.tMem node) - Node.nMem node
193
                   - Node.xMem node - Node.fMem node
194
        inc_icpu = Node.uCpu node
195
        inc_idsk = truncate (Node.tDsk node) - Node.fDsk node
196
        inc_vcpu = Node.hiCpu node
197
        inc_acpu = Node.availCpu node
198

    
199
    in cs { csFmem = x_fmem + Node.fMem node
200
          , csFdsk = x_fdsk + Node.fDsk node
201
          , csAmem = x_amem + inc_amem'
202
          , csAdsk = x_adsk + inc_adsk
203
          , csAcpu = x_acpu + inc_acpu
204
          , csMmem = max x_mmem inc_amem'
205
          , csMdsk = max x_mdsk inc_adsk
206
          , csMcpu = max x_mcpu inc_acpu
207
          , csImem = x_imem + inc_imem
208
          , csIdsk = x_idsk + inc_idsk
209
          , csIcpu = x_icpu + inc_icpu
210
          , csTmem = x_tmem + Node.tMem node
211
          , csTdsk = x_tdsk + Node.tDsk node
212
          , csTcpu = x_tcpu + Node.tCpu node
213
          , csVcpu = x_vcpu + inc_vcpu
214
          , csXmem = x_xmem + Node.xMem node
215
          , csNmem = x_nmem + Node.nMem node
216
          , csNinst = x_ninst + length (Node.pList node)
217
          }
218

    
219
-- | Compute the total free disk and memory in the cluster.
220
totalResources :: Node.List -> CStats
221
totalResources nl =
222
    let cs = foldl' updateCStats emptyCStats . Container.elems $ nl
223
    in cs { csScore = compCV nl }
224

    
225
-- | Compute the delta between two cluster state.
226
--
227
-- This is used when doing allocations, to understand better the
228
-- available cluster resources. The return value is a triple of the
229
-- current used values, the delta that was still allocated, and what
230
-- was left unallocated.
231
computeAllocationDelta :: CStats -> CStats -> AllocStats
232
computeAllocationDelta cini cfin =
233
    let CStats {csImem = i_imem, csIdsk = i_idsk, csIcpu = i_icpu} = cini
234
        CStats {csImem = f_imem, csIdsk = f_idsk, csIcpu = f_icpu,
235
                csTmem = t_mem, csTdsk = t_dsk, csVcpu = v_cpu } = cfin
236
        rini = RSpec i_icpu i_imem i_idsk
237
        rfin = RSpec (f_icpu - i_icpu) (f_imem - i_imem) (f_idsk - i_idsk)
238
        un_cpu = v_cpu - f_icpu
239
        runa = RSpec un_cpu (truncate t_mem - f_imem) (truncate t_dsk - f_idsk)
240
    in (rini, rfin, runa)
241

    
242
-- | The names and weights of the individual elements in the CV list
243
detailedCVInfo :: [(Double, String)]
244
detailedCVInfo = [ (1,  "free_mem_cv")
245
                 , (1,  "free_disk_cv")
246
                 , (1,  "n1_cnt")
247
                 , (1,  "reserved_mem_cv")
248
                 , (4,  "offline_all_cnt")
249
                 , (16, "offline_pri_cnt")
250
                 , (1,  "vcpu_ratio_cv")
251
                 , (1,  "cpu_load_cv")
252
                 , (1,  "mem_load_cv")
253
                 , (1,  "disk_load_cv")
254
                 , (1,  "net_load_cv")
255
                 , (2,  "pri_tags_score")
256
                 ]
257

    
258
detailedCVWeights :: [Double]
259
detailedCVWeights = map fst detailedCVInfo
260

    
261
-- | Compute the mem and disk covariance.
262
compDetailedCV :: Node.List -> [Double]
263
compDetailedCV nl =
264
    let
265
        all_nodes = Container.elems nl
266
        (offline, nodes) = partition Node.offline all_nodes
267
        mem_l = map Node.pMem nodes
268
        dsk_l = map Node.pDsk nodes
269
        -- metric: memory covariance
270
        mem_cv = stdDev mem_l
271
        -- metric: disk covariance
272
        dsk_cv = stdDev dsk_l
273
        -- metric: count of instances living on N1 failing nodes
274
        n1_score = fromIntegral . sum . map (\n -> length (Node.sList n) +
275
                                                   length (Node.pList n)) .
276
                   filter Node.failN1 $ nodes :: Double
277
        res_l = map Node.pRem nodes
278
        -- metric: reserved memory covariance
279
        res_cv = stdDev res_l
280
        -- offline instances metrics
281
        offline_ipri = sum . map (length . Node.pList) $ offline
282
        offline_isec = sum . map (length . Node.sList) $ offline
283
        -- metric: count of instances on offline nodes
284
        off_score = fromIntegral (offline_ipri + offline_isec)::Double
285
        -- metric: count of primary instances on offline nodes (this
286
        -- helps with evacuation/failover of primary instances on
287
        -- 2-node clusters with one node offline)
288
        off_pri_score = fromIntegral offline_ipri::Double
289
        cpu_l = map Node.pCpu nodes
290
        -- metric: covariance of vcpu/pcpu ratio
291
        cpu_cv = stdDev cpu_l
292
        -- metrics: covariance of cpu, memory, disk and network load
293
        (c_load, m_load, d_load, n_load) = unzip4 $
294
            map (\n ->
295
                     let DynUtil c1 m1 d1 n1 = Node.utilLoad n
296
                         DynUtil c2 m2 d2 n2 = Node.utilPool n
297
                     in (c1/c2, m1/m2, d1/d2, n1/n2)
298
                ) nodes
299
        -- metric: conflicting instance count
300
        pri_tags_inst = sum $ map Node.conflictingPrimaries nodes
301
        pri_tags_score = fromIntegral pri_tags_inst::Double
302
    in [ mem_cv, dsk_cv, n1_score, res_cv, off_score, off_pri_score, cpu_cv
303
       , stdDev c_load, stdDev m_load , stdDev d_load, stdDev n_load
304
       , pri_tags_score ]
305

    
306
-- | Compute the /total/ variance.
307
compCV :: Node.List -> Double
308
compCV = sum . zipWith (*) detailedCVWeights . compDetailedCV
309

    
310
-- | Compute online nodes from a Node.List
311
getOnline :: Node.List -> [Node.Node]
312
getOnline = filter (not . Node.offline) . Container.elems
313

    
314
-- * hbal functions
315

    
316
-- | Compute best table. Note that the ordering of the arguments is important.
317
compareTables :: Table -> Table -> Table
318
compareTables a@(Table _ _ a_cv _) b@(Table _ _ b_cv _ ) =
319
    if a_cv > b_cv then b else a
320

    
321
-- | Applies an instance move to a given node list and instance.
322
applyMove :: Node.List -> Instance.Instance
323
          -> IMove -> OpResult (Node.List, Instance.Instance, Ndx, Ndx)
324
-- Failover (f)
325
applyMove nl inst Failover =
326
    let old_pdx = Instance.pNode inst
327
        old_sdx = Instance.sNode inst
328
        old_p = Container.find old_pdx nl
329
        old_s = Container.find old_sdx nl
330
        int_p = Node.removePri old_p inst
331
        int_s = Node.removeSec old_s inst
332
        force_p = Node.offline old_p
333
        new_nl = do -- Maybe monad
334
          new_p <- Node.addPriEx force_p int_s inst
335
          new_s <- Node.addSec int_p inst old_sdx
336
          let new_inst = Instance.setBoth inst old_sdx old_pdx
337
          return (Container.addTwo old_pdx new_s old_sdx new_p nl,
338
                  new_inst, old_sdx, old_pdx)
339
    in new_nl
340

    
341
-- Replace the primary (f:, r:np, f)
342
applyMove nl inst (ReplacePrimary new_pdx) =
343
    let old_pdx = Instance.pNode inst
344
        old_sdx = Instance.sNode inst
345
        old_p = Container.find old_pdx nl
346
        old_s = Container.find old_sdx nl
347
        tgt_n = Container.find new_pdx nl
348
        int_p = Node.removePri old_p inst
349
        int_s = Node.removeSec old_s inst
350
        force_p = Node.offline old_p
351
        new_nl = do -- Maybe monad
352
          -- check that the current secondary can host the instance
353
          -- during the migration
354
          tmp_s <- Node.addPriEx force_p int_s inst
355
          let tmp_s' = Node.removePri tmp_s inst
356
          new_p <- Node.addPriEx force_p tgt_n inst
357
          new_s <- Node.addSecEx force_p tmp_s' inst new_pdx
358
          let new_inst = Instance.setPri inst new_pdx
359
          return (Container.add new_pdx new_p $
360
                  Container.addTwo old_pdx int_p old_sdx new_s nl,
361
                  new_inst, new_pdx, old_sdx)
362
    in new_nl
363

    
364
-- Replace the secondary (r:ns)
365
applyMove nl inst (ReplaceSecondary new_sdx) =
366
    let old_pdx = Instance.pNode inst
367
        old_sdx = Instance.sNode inst
368
        old_s = Container.find old_sdx nl
369
        tgt_n = Container.find new_sdx nl
370
        int_s = Node.removeSec old_s inst
371
        force_s = Node.offline old_s
372
        new_inst = Instance.setSec inst new_sdx
373
        new_nl = Node.addSecEx force_s tgt_n inst old_pdx >>=
374
                 \new_s -> return (Container.addTwo new_sdx
375
                                   new_s old_sdx int_s nl,
376
                                   new_inst, old_pdx, new_sdx)
377
    in new_nl
378

    
379
-- Replace the secondary and failover (r:np, f)
380
applyMove nl inst (ReplaceAndFailover new_pdx) =
381
    let old_pdx = Instance.pNode inst
382
        old_sdx = Instance.sNode inst
383
        old_p = Container.find old_pdx nl
384
        old_s = Container.find old_sdx nl
385
        tgt_n = Container.find new_pdx nl
386
        int_p = Node.removePri old_p inst
387
        int_s = Node.removeSec old_s inst
388
        force_s = Node.offline old_s
389
        new_nl = do -- Maybe monad
390
          new_p <- Node.addPri tgt_n inst
391
          new_s <- Node.addSecEx force_s int_p inst new_pdx
392
          let new_inst = Instance.setBoth inst new_pdx old_pdx
393
          return (Container.add new_pdx new_p $
394
                  Container.addTwo old_pdx new_s old_sdx int_s nl,
395
                  new_inst, new_pdx, old_pdx)
396
    in new_nl
397

    
398
-- Failver and replace the secondary (f, r:ns)
399
applyMove nl inst (FailoverAndReplace new_sdx) =
400
    let old_pdx = Instance.pNode inst
401
        old_sdx = Instance.sNode inst
402
        old_p = Container.find old_pdx nl
403
        old_s = Container.find old_sdx nl
404
        tgt_n = Container.find new_sdx nl
405
        int_p = Node.removePri old_p inst
406
        int_s = Node.removeSec old_s inst
407
        force_p = Node.offline old_p
408
        new_nl = do -- Maybe monad
409
          new_p <- Node.addPriEx force_p int_s inst
410
          new_s <- Node.addSecEx force_p tgt_n inst old_sdx
411
          let new_inst = Instance.setBoth inst old_sdx new_sdx
412
          return (Container.add new_sdx new_s $
413
                  Container.addTwo old_sdx new_p old_pdx int_p nl,
414
                  new_inst, old_sdx, new_sdx)
415
    in new_nl
416

    
417
-- | Tries to allocate an instance on one given node.
418
allocateOnSingle :: Node.List -> Instance.Instance -> Ndx
419
                 -> OpResult Node.AllocElement
420
allocateOnSingle nl inst new_pdx =
421
    let p = Container.find new_pdx nl
422
        new_inst = Instance.setBoth inst new_pdx Node.noSecondary
423
    in  Node.addPri p inst >>= \new_p -> do
424
      let new_nl = Container.add new_pdx new_p nl
425
          new_score = compCV nl
426
      return (new_nl, new_inst, [new_p], new_score)
427

    
428
-- | Tries to allocate an instance on a given pair of nodes.
429
allocateOnPair :: Node.List -> Instance.Instance -> Ndx -> Ndx
430
               -> OpResult Node.AllocElement
431
allocateOnPair nl inst new_pdx new_sdx =
432
    let tgt_p = Container.find new_pdx nl
433
        tgt_s = Container.find new_sdx nl
434
    in do
435
      new_p <- Node.addPri tgt_p inst
436
      new_s <- Node.addSec tgt_s inst new_pdx
437
      let new_inst = Instance.setBoth inst new_pdx new_sdx
438
          new_nl = Container.addTwo new_pdx new_p new_sdx new_s nl
439
      return (new_nl, new_inst, [new_p, new_s], compCV new_nl)
440

    
441
-- | Tries to perform an instance move and returns the best table
442
-- between the original one and the new one.
443
checkSingleStep :: Table -- ^ The original table
444
                -> Instance.Instance -- ^ The instance to move
445
                -> Table -- ^ The current best table
446
                -> IMove -- ^ The move to apply
447
                -> Table -- ^ The final best table
448
checkSingleStep ini_tbl target cur_tbl move =
449
    let
450
        Table ini_nl ini_il _ ini_plc = ini_tbl
451
        tmp_resu = applyMove ini_nl target move
452
    in
453
      case tmp_resu of
454
        OpFail _ -> cur_tbl
455
        OpGood (upd_nl, new_inst, pri_idx, sec_idx) ->
456
            let tgt_idx = Instance.idx target
457
                upd_cvar = compCV upd_nl
458
                upd_il = Container.add tgt_idx new_inst ini_il
459
                upd_plc = (tgt_idx, pri_idx, sec_idx, move, upd_cvar):ini_plc
460
                upd_tbl = Table upd_nl upd_il upd_cvar upd_plc
461
            in
462
              compareTables cur_tbl upd_tbl
463

    
464
-- | Given the status of the current secondary as a valid new node and
465
-- the current candidate target node, generate the possible moves for
466
-- a instance.
467
possibleMoves :: Bool      -- ^ Whether the secondary node is a valid new node
468
              -> Bool      -- ^ Whether we can change the primary node
469
              -> Ndx       -- ^ Target node candidate
470
              -> [IMove]   -- ^ List of valid result moves
471

    
472
possibleMoves _ False tdx =
473
    [ReplaceSecondary tdx]
474

    
475
possibleMoves True True tdx =
476
    [ReplaceSecondary tdx,
477
     ReplaceAndFailover tdx,
478
     ReplacePrimary tdx,
479
     FailoverAndReplace tdx]
480

    
481
possibleMoves False True tdx =
482
    [ReplaceSecondary tdx,
483
     ReplaceAndFailover tdx]
484

    
485
-- | Compute the best move for a given instance.
486
checkInstanceMove :: [Ndx]             -- ^ Allowed target node indices
487
                  -> Bool              -- ^ Whether disk moves are allowed
488
                  -> Bool              -- ^ Whether instance moves are allowed
489
                  -> Table             -- ^ Original table
490
                  -> Instance.Instance -- ^ Instance to move
491
                  -> Table             -- ^ Best new table for this instance
492
checkInstanceMove nodes_idx disk_moves inst_moves ini_tbl target =
493
    let
494
        opdx = Instance.pNode target
495
        osdx = Instance.sNode target
496
        nodes = filter (\idx -> idx /= opdx && idx /= osdx) nodes_idx
497
        use_secondary = elem osdx nodes_idx && inst_moves
498
        aft_failover = if use_secondary -- if allowed to failover
499
                       then checkSingleStep ini_tbl target ini_tbl Failover
500
                       else ini_tbl
501
        all_moves = if disk_moves
502
                    then concatMap
503
                         (possibleMoves use_secondary inst_moves) nodes
504
                    else []
505
    in
506
      -- iterate over the possible nodes for this instance
507
      foldl' (checkSingleStep ini_tbl target) aft_failover all_moves
508

    
509
-- | Compute the best next move.
510
checkMove :: [Ndx]               -- ^ Allowed target node indices
511
          -> Bool                -- ^ Whether disk moves are allowed
512
          -> Bool                -- ^ Whether instance moves are allowed
513
          -> Table               -- ^ The current solution
514
          -> [Instance.Instance] -- ^ List of instances still to move
515
          -> Table               -- ^ The new solution
516
checkMove nodes_idx disk_moves inst_moves ini_tbl victims =
517
    let Table _ _ _ ini_plc = ini_tbl
518
        -- we're using rwhnf from the Control.Parallel.Strategies
519
        -- package; we don't need to use rnf as that would force too
520
        -- much evaluation in single-threaded cases, and in
521
        -- multi-threaded case the weak head normal form is enough to
522
        -- spark the evaluation
523
        tables = parMap rwhnf (checkInstanceMove nodes_idx disk_moves
524
                               inst_moves ini_tbl)
525
                 victims
526
        -- iterate over all instances, computing the best move
527
        best_tbl = foldl' compareTables ini_tbl tables
528
        Table _ _ _ best_plc = best_tbl
529
    in if length best_plc == length ini_plc
530
       then ini_tbl -- no advancement
531
       else best_tbl
532

    
533
-- | Check if we are allowed to go deeper in the balancing
534
doNextBalance :: Table     -- ^ The starting table
535
              -> Int       -- ^ Remaining length
536
              -> Score     -- ^ Score at which to stop
537
              -> Bool      -- ^ The resulting table and commands
538
doNextBalance ini_tbl max_rounds min_score =
539
    let Table _ _ ini_cv ini_plc = ini_tbl
540
        ini_plc_len = length ini_plc
541
    in (max_rounds < 0 || ini_plc_len < max_rounds) && ini_cv > min_score
542

    
543
-- | Run a balance move
544
tryBalance :: Table       -- ^ The starting table
545
           -> Bool        -- ^ Allow disk moves
546
           -> Bool        -- ^ Allow instance moves
547
           -> Bool        -- ^ Only evacuate moves
548
           -> Score       -- ^ Min gain threshold
549
           -> Score       -- ^ Min gain
550
           -> Maybe Table -- ^ The resulting table and commands
551
tryBalance ini_tbl disk_moves inst_moves evac_mode mg_limit min_gain =
552
    let Table ini_nl ini_il ini_cv _ = ini_tbl
553
        all_inst = Container.elems ini_il
554
        all_inst' = if evac_mode
555
                    then let bad_nodes = map Node.idx . filter Node.offline $
556
                                         Container.elems ini_nl
557
                         in filter (\e -> Instance.sNode e `elem` bad_nodes ||
558
                                          Instance.pNode e `elem` bad_nodes)
559
                            all_inst
560
                    else all_inst
561
        reloc_inst = filter Instance.movable all_inst'
562
        node_idx = map Node.idx . filter (not . Node.offline) $
563
                   Container.elems ini_nl
564
        fin_tbl = checkMove node_idx disk_moves inst_moves ini_tbl reloc_inst
565
        (Table _ _ fin_cv _) = fin_tbl
566
    in
567
      if fin_cv < ini_cv && (ini_cv > mg_limit || ini_cv - fin_cv >= min_gain)
568
      then Just fin_tbl -- this round made success, return the new table
569
      else Nothing
570

    
571
-- * Allocation functions
572

    
573
-- | Build failure stats out of a list of failures
574
collapseFailures :: [FailMode] -> FailStats
575
collapseFailures flst =
576
    map (\k -> (k, length $ filter (k ==) flst)) [minBound..maxBound]
577

    
578
-- | Update current Allocation solution and failure stats with new
579
-- elements
580
concatAllocs :: AllocSolution -> OpResult Node.AllocElement -> AllocSolution
581
concatAllocs as (OpFail reason) = as { asFailures = reason : asFailures as }
582

    
583
concatAllocs as (OpGood ns@(_, _, _, nscore)) =
584
    let -- Choose the old or new solution, based on the cluster score
585
        cntok = asAllocs as
586
        osols = asSolutions as
587
        nsols = case osols of
588
                  [] -> [ns]
589
                  (_, _, _, oscore):[] ->
590
                      if oscore < nscore
591
                      then osols
592
                      else [ns]
593
                  -- FIXME: here we simply concat to lists with more
594
                  -- than one element; we should instead abort, since
595
                  -- this is not a valid usage of this function
596
                  xs -> ns:xs
597
        nsuc = cntok + 1
598
    -- Note: we force evaluation of nsols here in order to keep the
599
    -- memory profile low - we know that we will need nsols for sure
600
    -- in the next cycle, so we force evaluation of nsols, since the
601
    -- foldl' in the caller will only evaluate the tuple, but not the
602
    -- elements of the tuple
603
    in nsols `seq` nsuc `seq` as { asAllocs = nsuc, asSolutions = nsols }
604

    
605
-- | Sums two allocation solutions (e.g. for two separate node groups).
606
sumAllocs :: AllocSolution -> AllocSolution -> AllocSolution
607
sumAllocs (AllocSolution af aa as al) (AllocSolution bf ba bs bl) =
608
    AllocSolution (af ++ bf) (aa + ba) (as ++ bs) (al ++ bl)
609

    
610
-- | Given a solution, generates a reasonable description for it
611
describeSolution :: AllocSolution -> String
612
describeSolution as =
613
  let fcnt = asFailures as
614
      sols = asSolutions as
615
      freasons =
616
        intercalate ", " . map (\(a, b) -> printf "%s: %d" (show a) b) .
617
        filter ((> 0) . snd) . collapseFailures $ fcnt
618
  in if null sols
619
     then "No valid allocation solutions, failure reasons: " ++
620
          (if null fcnt
621
           then "unknown reasons"
622
           else freasons)
623
     else let (_, _, nodes, cv) = head sols
624
          in printf ("score: %.8f, successes %d, failures %d (%s)" ++
625
                     " for node(s) %s") cv (asAllocs as) (length fcnt) freasons
626
             (intercalate "/" . map Node.name $ nodes)
627

    
628
-- | Annotates a solution with the appropriate string
629
annotateSolution :: AllocSolution -> AllocSolution
630
annotateSolution as = as { asLog = describeSolution as : asLog as }
631

    
632
-- | Generate the valid node allocation singles or pairs for a new instance.
633
genAllocNodes :: Group.List        -- ^ Group list
634
              -> Node.List         -- ^ The node map
635
              -> Int               -- ^ The number of nodes required
636
              -> Bool              -- ^ Whether to drop or not
637
                                   -- unallocable nodes
638
              -> Result AllocNodes -- ^ The (monadic) result
639
genAllocNodes gl nl count drop_unalloc =
640
    let filter_fn = if drop_unalloc
641
                    then filter (Group.isAllocable .
642
                                 flip Container.find gl . Node.group)
643
                    else id
644
        all_nodes = filter_fn $ getOnline nl
645
        all_pairs = liftM2 (,) all_nodes all_nodes
646
        ok_pairs = filter (\(x, y) -> Node.idx x /= Node.idx y &&
647
                                      Node.group x == Node.group y) all_pairs
648
    in case count of
649
         1 -> Ok (Left (map Node.idx all_nodes))
650
         2 -> Ok (Right (map (\(p, s) -> (Node.idx p, Node.idx s)) ok_pairs))
651
         _ -> Bad "Unsupported number of nodes, only one or two  supported"
652

    
653
-- | Try to allocate an instance on the cluster.
654
tryAlloc :: (Monad m) =>
655
            Node.List         -- ^ The node list
656
         -> Instance.List     -- ^ The instance list
657
         -> Instance.Instance -- ^ The instance to allocate
658
         -> AllocNodes        -- ^ The allocation targets
659
         -> m AllocSolution   -- ^ Possible solution list
660
tryAlloc nl _ inst (Right ok_pairs) =
661
    let sols = foldl' (\cstate (p, s) ->
662
                           concatAllocs cstate $ allocateOnPair nl inst p s
663
                      ) emptySolution ok_pairs
664

    
665
    in if null ok_pairs -- means we have just one node
666
       then fail "Not enough online nodes"
667
       else return $ annotateSolution sols
668

    
669
tryAlloc nl _ inst (Left all_nodes) =
670
    let sols = foldl' (\cstate ->
671
                           concatAllocs cstate . allocateOnSingle nl inst
672
                      ) emptySolution all_nodes
673
    in if null all_nodes
674
       then fail "No online nodes"
675
       else return $ annotateSolution sols
676

    
677
-- | Given a group/result, describe it as a nice (list of) messages
678
solutionDescription :: Group.List -> (Gdx, Result AllocSolution) -> [String]
679
solutionDescription gl (groupId, result) =
680
  case result of
681
    Ok solution -> map (printf "Group %s (%s): %s" gname pol) (asLog solution)
682
    Bad message -> [printf "Group %s: error %s" gname message]
683
  where grp = Container.find groupId gl
684
        gname = Group.name grp
685
        pol = apolToString (Group.allocPolicy grp)
686

    
687
-- | From a list of possibly bad and possibly empty solutions, filter
688
-- only the groups with a valid result
689
filterMGResults :: Group.List
690
                -> [(Gdx, Result AllocSolution)]
691
                -> [(Gdx, AllocSolution)]
692
filterMGResults gl=
693
  filter ((/= AllocUnallocable) . Group.allocPolicy .
694
             flip Container.find gl . fst) .
695
  filter (not . null . asSolutions . snd) .
696
  map (\(y, Ok x) -> (y, x)) .
697
  filter (isOk . snd)
698

    
699
-- | Sort multigroup results based on policy and score
700
sortMGResults :: Group.List
701
             -> [(Gdx, AllocSolution)]
702
             -> [(Gdx, AllocSolution)]
703
sortMGResults gl sols =
704
    let extractScore (_, _, _, x) = x
705
        solScore (gdx, sol) = (Group.allocPolicy (Container.find gdx gl),
706
                               (extractScore . head . asSolutions) sol)
707
    in sortBy (comparing solScore) sols
708

    
709
-- | Try to allocate an instance on a multi-group cluster.
710
tryMGAlloc :: Group.List           -- ^ The group list
711
           -> Node.List            -- ^ The node list
712
           -> Instance.List        -- ^ The instance list
713
           -> Instance.Instance    -- ^ The instance to allocate
714
           -> Int                  -- ^ Required number of nodes
715
           -> Result AllocSolution -- ^ Possible solution list
716
tryMGAlloc mggl mgnl mgil inst cnt =
717
  let groups = splitCluster mgnl mgil
718
      sols = map (\(gid, (nl, il)) ->
719
                   (gid, genAllocNodes mggl nl cnt False >>=
720
                       tryAlloc nl il inst))
721
             groups::[(Gdx, Result AllocSolution)]
722
      all_msgs = concatMap (solutionDescription mggl) sols
723
      goodSols = filterMGResults mggl sols
724
      sortedSols = sortMGResults mggl goodSols
725
  in if null sortedSols
726
     then Bad $ intercalate ", " all_msgs
727
     else let (final_group, final_sol) = head sortedSols
728
              final_name = Group.name $ Container.find final_group mggl
729
              selmsg = "Selected group: " ++  final_name
730
          in Ok $ final_sol { asLog = selmsg:all_msgs }
731

    
732
-- | Try to relocate an instance on the cluster.
733
tryReloc :: (Monad m) =>
734
            Node.List       -- ^ The node list
735
         -> Instance.List   -- ^ The instance list
736
         -> Idx             -- ^ The index of the instance to move
737
         -> Int             -- ^ The number of nodes required
738
         -> [Ndx]           -- ^ Nodes which should not be used
739
         -> m AllocSolution -- ^ Solution list
740
tryReloc nl il xid 1 ex_idx =
741
    let all_nodes = getOnline nl
742
        inst = Container.find xid il
743
        ex_idx' = Instance.pNode inst:ex_idx
744
        valid_nodes = filter (not . flip elem ex_idx' . Node.idx) all_nodes
745
        valid_idxes = map Node.idx valid_nodes
746
        sols1 = foldl' (\cstate x ->
747
                            let em = do
748
                                  (mnl, i, _, _) <-
749
                                      applyMove nl inst (ReplaceSecondary x)
750
                                  return (mnl, i, [Container.find x mnl],
751
                                          compCV mnl)
752
                            in concatAllocs cstate em
753
                       ) emptySolution valid_idxes
754
    in return sols1
755

    
756
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
757
                                \destinations required (" ++ show reqn ++
758
                                                  "), only one supported"
759

    
760
tryMGReloc :: (Monad m) =>
761
              Group.List      -- ^ The group list
762
           -> Node.List       -- ^ The node list
763
           -> Instance.List   -- ^ The instance list
764
           -> Idx             -- ^ The index of the instance to move
765
           -> Int             -- ^ The number of nodes required
766
           -> [Ndx]           -- ^ Nodes which should not be used
767
           -> m AllocSolution -- ^ Solution list
768
tryMGReloc _ mgnl mgil xid ncount ex_ndx = do
769
  let groups = splitCluster mgnl mgil
770
      -- TODO: we only relocate inside the group for now
771
      inst = Container.find xid mgil
772
  (nl, il) <- case lookup (instancePriGroup mgnl inst) groups of
773
                Nothing -> fail $ "Cannot find group for instance " ++
774
                           Instance.name inst
775
                Just v -> return v
776
  tryReloc nl il xid ncount ex_ndx
777

    
778
-- | Change an instance's secondary node
779
evacInstance :: (Monad m) =>
780
                [Ndx]                      -- ^ Excluded nodes
781
             -> Instance.List              -- ^ The current instance list
782
             -> (Node.List, AllocSolution) -- ^ The current state
783
             -> Idx                        -- ^ The instance to evacuate
784
             -> m (Node.List, AllocSolution)
785
evacInstance ex_ndx il (nl, old_as) idx = do
786
  -- FIXME: hardcoded one node here
787

    
788
  -- Longer explanation: evacuation is currently hardcoded to DRBD
789
  -- instances (which have one secondary); hence, even if the
790
  -- IAllocator protocol can request N nodes for an instance, and all
791
  -- the message parsing/loading pass this, this implementation only
792
  -- supports one; this situation needs to be revisited if we ever
793
  -- support more than one secondary, or if we change the storage
794
  -- model
795
  new_as <- tryReloc nl il idx 1 ex_ndx
796
  case asSolutions new_as of
797
    -- an individual relocation succeeded, we kind of compose the data
798
    -- from the two solutions
799
    csol@(nl', _, _, _):_ ->
800
        return (nl', new_as { asSolutions = csol:asSolutions old_as })
801
    -- this relocation failed, so we fail the entire evac
802
    _ -> fail $ "Can't evacuate instance " ++
803
         Instance.name (Container.find idx il) ++
804
             ": " ++ describeSolution new_as
805

    
806
-- | Try to evacuate a list of nodes.
807
tryEvac :: (Monad m) =>
808
            Node.List       -- ^ The node list
809
         -> Instance.List   -- ^ The instance list
810
         -> [Idx]           -- ^ Instances to be evacuated
811
         -> [Ndx]           -- ^ Restricted nodes (the ones being evacuated)
812
         -> m AllocSolution -- ^ Solution list
813
tryEvac nl il idxs ex_ndx = do
814
  (_, sol) <- foldM (evacInstance ex_ndx il) (nl, emptySolution) idxs
815
  return sol
816

    
817
-- | Multi-group evacuation of a list of nodes.
818
tryMGEvac :: (Monad m) =>
819
             Group.List -- ^ The group list
820
          -> Node.List       -- ^ The node list
821
          -> Instance.List   -- ^ The instance list
822
          -> [Ndx]           -- ^ Nodes to be evacuated
823
          -> m AllocSolution -- ^ Solution list
824
tryMGEvac _ nl il ex_ndx =
825
    let ex_nodes = map (`Container.find` nl) ex_ndx
826
        all_insts = nub . concatMap Node.sList $ ex_nodes
827
        gni = splitCluster nl il
828
        -- we run the instance index list through a couple of maps to
829
        -- get finally to a structure of the type [(group index,
830
        -- [instance indices])]
831
        all_insts' = map (\idx ->
832
                              (instancePriGroup nl (Container.find idx il),
833
                               idx)) all_insts
834
        all_insts'' = groupBy ((==) `on` fst) all_insts'
835
        all_insts3 = map (\xs -> let (gdxs, idxs) = unzip xs
836
                                 in (head gdxs, idxs)) all_insts''
837
    in do
838
      -- that done, we now add the per-group nl/il to the tuple
839
      all_insts4 <-
840
          mapM (\(gdx, idxs) ->
841
                case lookup gdx gni of
842
                    Nothing -> fail $ "Can't find group index " ++ show gdx
843
                    Just (gnl, gil) -> return (gdx, gnl, gil, idxs))
844
          all_insts3
845
      results <- mapM (\(_, gnl, gil, idxs) -> tryEvac gnl gil idxs ex_ndx)
846
                 all_insts4
847
      let sol = foldl' sumAllocs emptySolution results
848
      return $ annotateSolution sol
849

    
850
-- | Recursively place instances on the cluster until we're out of space
851
iterateAlloc :: Node.List
852
             -> Instance.List
853
             -> Instance.Instance
854
             -> AllocNodes
855
             -> [Instance.Instance]
856
             -> [CStats]
857
             -> Result AllocResult
858
iterateAlloc nl il newinst allocnodes ixes cstats =
859
      let depth = length ixes
860
          newname = printf "new-%d" depth::String
861
          newidx = length (Container.elems il) + depth
862
          newi2 = Instance.setIdx (Instance.setName newinst newname) newidx
863
      in case tryAlloc nl il newi2 allocnodes of
864
           Bad s -> Bad s
865
           Ok (AllocSolution { asFailures = errs, asSolutions = sols3 }) ->
866
               case sols3 of
867
                 [] -> Ok (collapseFailures errs, nl, il, ixes, cstats)
868
                 (xnl, xi, _, _):[] ->
869
                     iterateAlloc xnl (Container.add newidx xi il)
870
                                  newinst allocnodes (xi:ixes)
871
                                  (totalResources xnl:cstats)
872
                 _ -> Bad "Internal error: multiple solutions for single\
873
                          \ allocation"
874

    
875
-- | The core of the tiered allocation mode
876
tieredAlloc :: Node.List
877
            -> Instance.List
878
            -> Instance.Instance
879
            -> AllocNodes
880
            -> [Instance.Instance]
881
            -> [CStats]
882
            -> Result AllocResult
883
tieredAlloc nl il newinst allocnodes ixes cstats =
884
    case iterateAlloc nl il newinst allocnodes ixes cstats of
885
      Bad s -> Bad s
886
      Ok (errs, nl', il', ixes', cstats') ->
887
          case Instance.shrinkByType newinst . fst . last $
888
               sortBy (comparing snd) errs of
889
            Bad _ -> Ok (errs, nl', il', ixes', cstats')
890
            Ok newinst' ->
891
                tieredAlloc nl' il' newinst' allocnodes ixes' cstats'
892

    
893
-- | Compute the tiered spec string description from a list of
894
-- allocated instances.
895
tieredSpecMap :: [Instance.Instance]
896
              -> [String]
897
tieredSpecMap trl_ixes =
898
    let fin_trl_ixes = reverse trl_ixes
899
        ix_byspec = groupBy ((==) `on` Instance.specOf) fin_trl_ixes
900
        spec_map = map (\ixs -> (Instance.specOf $ head ixs, length ixs))
901
                   ix_byspec
902
    in  map (\(spec, cnt) -> printf "%d,%d,%d=%d" (rspecMem spec)
903
                             (rspecDsk spec) (rspecCpu spec) cnt) spec_map
904

    
905
-- * Formatting functions
906

    
907
-- | Given the original and final nodes, computes the relocation description.
908
computeMoves :: Instance.Instance -- ^ The instance to be moved
909
             -> String -- ^ The instance name
910
             -> IMove  -- ^ The move being performed
911
             -> String -- ^ New primary
912
             -> String -- ^ New secondary
913
             -> (String, [String])
914
                -- ^ Tuple of moves and commands list; moves is containing
915
                -- either @/f/@ for failover or @/r:name/@ for replace
916
                -- secondary, while the command list holds gnt-instance
917
                -- commands (without that prefix), e.g \"@failover instance1@\"
918
computeMoves i inam mv c d =
919
    case mv of
920
      Failover -> ("f", [mig])
921
      FailoverAndReplace _ -> (printf "f r:%s" d, [mig, rep d])
922
      ReplaceSecondary _ -> (printf "r:%s" d, [rep d])
923
      ReplaceAndFailover _ -> (printf "r:%s f" c, [rep c, mig])
924
      ReplacePrimary _ -> (printf "f r:%s f" c, [mig, rep c, mig])
925
    where morf = if Instance.running i then "migrate" else "failover"
926
          mig = printf "%s -f %s" morf inam::String
927
          rep n = printf "replace-disks -n %s %s" n inam
928

    
929
-- | Converts a placement to string format.
930
printSolutionLine :: Node.List     -- ^ The node list
931
                  -> Instance.List -- ^ The instance list
932
                  -> Int           -- ^ Maximum node name length
933
                  -> Int           -- ^ Maximum instance name length
934
                  -> Placement     -- ^ The current placement
935
                  -> Int           -- ^ The index of the placement in
936
                                   -- the solution
937
                  -> (String, [String])
938
printSolutionLine nl il nmlen imlen plc pos =
939
    let
940
        pmlen = (2*nmlen + 1)
941
        (i, p, s, mv, c) = plc
942
        inst = Container.find i il
943
        inam = Instance.alias inst
944
        npri = Node.alias $ Container.find p nl
945
        nsec = Node.alias $ Container.find s nl
946
        opri = Node.alias $ Container.find (Instance.pNode inst) nl
947
        osec = Node.alias $ Container.find (Instance.sNode inst) nl
948
        (moves, cmds) =  computeMoves inst inam mv npri nsec
949
        ostr = printf "%s:%s" opri osec::String
950
        nstr = printf "%s:%s" npri nsec::String
951
    in
952
      (printf "  %3d. %-*s %-*s => %-*s %.8f a=%s"
953
       pos imlen inam pmlen ostr
954
       pmlen nstr c moves,
955
       cmds)
956

    
957
-- | Return the instance and involved nodes in an instance move.
958
involvedNodes :: Instance.List -> Placement -> [Ndx]
959
involvedNodes il plc =
960
    let (i, np, ns, _, _) = plc
961
        inst = Container.find i il
962
        op = Instance.pNode inst
963
        os = Instance.sNode inst
964
    in nub [np, ns, op, os]
965

    
966
-- | Inner function for splitJobs, that either appends the next job to
967
-- the current jobset, or starts a new jobset.
968
mergeJobs :: ([JobSet], [Ndx]) -> MoveJob -> ([JobSet], [Ndx])
969
mergeJobs ([], _) n@(ndx, _, _, _) = ([[n]], ndx)
970
mergeJobs (cjs@(j:js), nbuf) n@(ndx, _, _, _)
971
    | null (ndx `intersect` nbuf) = ((n:j):js, ndx ++ nbuf)
972
    | otherwise = ([n]:cjs, ndx)
973

    
974
-- | Break a list of moves into independent groups. Note that this
975
-- will reverse the order of jobs.
976
splitJobs :: [MoveJob] -> [JobSet]
977
splitJobs = fst . foldl mergeJobs ([], [])
978

    
979
-- | Given a list of commands, prefix them with @gnt-instance@ and
980
-- also beautify the display a little.
981
formatJob :: Int -> Int -> (Int, MoveJob) -> [String]
982
formatJob jsn jsl (sn, (_, _, _, cmds)) =
983
    let out =
984
            printf "  echo job %d/%d" jsn sn:
985
            printf "  check":
986
            map ("  gnt-instance " ++) cmds
987
    in if sn == 1
988
       then ["", printf "echo jobset %d, %d jobs" jsn jsl] ++ out
989
       else out
990

    
991
-- | Given a list of commands, prefix them with @gnt-instance@ and
992
-- also beautify the display a little.
993
formatCmds :: [JobSet] -> String
994
formatCmds =
995
    unlines .
996
    concatMap (\(jsn, js) -> concatMap (formatJob jsn (length js))
997
                             (zip [1..] js)) .
998
    zip [1..]
999

    
1000
-- | Print the node list.
1001
printNodes :: Node.List -> [String] -> String
1002
printNodes nl fs =
1003
    let fields = case fs of
1004
          [] -> Node.defaultFields
1005
          "+":rest -> Node.defaultFields ++ rest
1006
          _ -> fs
1007
        snl = sortBy (comparing Node.idx) (Container.elems nl)
1008
        (header, isnum) = unzip $ map Node.showHeader fields
1009
    in unlines . map ((:) ' ' .  intercalate " ") $
1010
       formatTable (header:map (Node.list fields) snl) isnum
1011

    
1012
-- | Print the instance list.
1013
printInsts :: Node.List -> Instance.List -> String
1014
printInsts nl il =
1015
    let sil = sortBy (comparing Instance.idx) (Container.elems il)
1016
        helper inst = [ if Instance.running inst then "R" else " "
1017
                      , Instance.name inst
1018
                      , Container.nameOf nl (Instance.pNode inst)
1019
                      , let sdx = Instance.sNode inst
1020
                        in if sdx == Node.noSecondary
1021
                           then  ""
1022
                           else Container.nameOf nl sdx
1023
                      , if Instance.auto_balance inst then "Y" else "N"
1024
                      , printf "%3d" $ Instance.vcpus inst
1025
                      , printf "%5d" $ Instance.mem inst
1026
                      , printf "%5d" $ Instance.dsk inst `div` 1024
1027
                      , printf "%5.3f" lC
1028
                      , printf "%5.3f" lM
1029
                      , printf "%5.3f" lD
1030
                      , printf "%5.3f" lN
1031
                      ]
1032
            where DynUtil lC lM lD lN = Instance.util inst
1033
        header = [ "F", "Name", "Pri_node", "Sec_node", "Auto_bal"
1034
                 , "vcpu", "mem" , "dsk", "lCpu", "lMem", "lDsk", "lNet" ]
1035
        isnum = False:False:False:False:False:repeat True
1036
    in unlines . map ((:) ' ' . intercalate " ") $
1037
       formatTable (header:map helper sil) isnum
1038

    
1039
-- | Shows statistics for a given node list.
1040
printStats :: Node.List -> String
1041
printStats nl =
1042
    let dcvs = compDetailedCV nl
1043
        (weights, names) = unzip detailedCVInfo
1044
        hd = zip3 (weights ++ repeat 1) (names ++ repeat "unknown") dcvs
1045
        formatted = map (\(w, header, val) ->
1046
                             printf "%s=%.8f(x%.2f)" header val w::String) hd
1047
    in intercalate ", " formatted
1048

    
1049
-- | Convert a placement into a list of OpCodes (basically a job).
1050
iMoveToJob :: Node.List -> Instance.List
1051
          -> Idx -> IMove -> [OpCodes.OpCode]
1052
iMoveToJob nl il idx move =
1053
    let inst = Container.find idx il
1054
        iname = Instance.name inst
1055
        lookNode  = Just . Container.nameOf nl
1056
        opF = OpCodes.OpInstanceMigrate iname True False True
1057
        opR n = OpCodes.OpInstanceReplaceDisks iname (lookNode n)
1058
                OpCodes.ReplaceNewSecondary [] Nothing
1059
    in case move of
1060
         Failover -> [ opF ]
1061
         ReplacePrimary np -> [ opF, opR np, opF ]
1062
         ReplaceSecondary ns -> [ opR ns ]
1063
         ReplaceAndFailover np -> [ opR np, opF ]
1064
         FailoverAndReplace ns -> [ opF, opR ns ]
1065

    
1066
-- * Node group functions
1067

    
1068
-- | Computes the group of an instance
1069
instanceGroup :: Node.List -> Instance.Instance -> Result Gdx
1070
instanceGroup nl i =
1071
  let sidx = Instance.sNode i
1072
      pnode = Container.find (Instance.pNode i) nl
1073
      snode = if sidx == Node.noSecondary
1074
              then pnode
1075
              else Container.find sidx nl
1076
      pgroup = Node.group pnode
1077
      sgroup = Node.group snode
1078
  in if pgroup /= sgroup
1079
     then fail ("Instance placed accross two node groups, primary " ++
1080
                show pgroup ++ ", secondary " ++ show sgroup)
1081
     else return pgroup
1082

    
1083
-- | Computes the group of an instance per the primary node
1084
instancePriGroup :: Node.List -> Instance.Instance -> Gdx
1085
instancePriGroup nl i =
1086
  let pnode = Container.find (Instance.pNode i) nl
1087
  in  Node.group pnode
1088

    
1089
-- | Compute the list of badly allocated instances (split across node
1090
-- groups)
1091
findSplitInstances :: Node.List -> Instance.List -> [Instance.Instance]
1092
findSplitInstances nl =
1093
  filter (not . isOk . instanceGroup nl) . Container.elems
1094

    
1095
-- | Splits a cluster into the component node groups
1096
splitCluster :: Node.List -> Instance.List ->
1097
                [(Gdx, (Node.List, Instance.List))]
1098
splitCluster nl il =
1099
  let ngroups = Node.computeGroups (Container.elems nl)
1100
  in map (\(guuid, nodes) ->
1101
           let nidxs = map Node.idx nodes
1102
               nodes' = zip nidxs nodes
1103
               instances = Container.filter ((`elem` nidxs) . Instance.pNode) il
1104
           in (guuid, (Container.fromList nodes', instances))) ngroups