Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (45.6 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
              -> Ndx       -- ^ Target node candidate
469
              -> [IMove]   -- ^ List of valid result moves
470
possibleMoves True tdx =
471
    [ReplaceSecondary tdx,
472
     ReplaceAndFailover tdx,
473
     ReplacePrimary tdx,
474
     FailoverAndReplace tdx]
475

    
476
possibleMoves False tdx =
477
    [ReplaceSecondary tdx,
478
     ReplaceAndFailover tdx]
479

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

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

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

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

    
564
-- * Allocation functions
565

    
566
-- | Build failure stats out of a list of failures
567
collapseFailures :: [FailMode] -> FailStats
568
collapseFailures flst =
569
    map (\k -> (k, length $ filter (k ==) flst)) [minBound..maxBound]
570

    
571
-- | Update current Allocation solution and failure stats with new
572
-- elements
573
concatAllocs :: AllocSolution -> OpResult Node.AllocElement -> AllocSolution
574
concatAllocs as (OpFail reason) = as { asFailures = reason : asFailures as }
575

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

    
598
-- | Sums two allocation solutions (e.g. for two separate node groups).
599
sumAllocs :: AllocSolution -> AllocSolution -> AllocSolution
600
sumAllocs (AllocSolution af aa as al) (AllocSolution bf ba bs bl) =
601
    AllocSolution (af ++ bf) (aa + ba) (as ++ bs) (al ++ bl)
602

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

    
621
-- | Annotates a solution with the appropriate string
622
annotateSolution :: AllocSolution -> AllocSolution
623
annotateSolution as = as { asLog = describeSolution as : asLog as }
624

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

    
646
-- | Try to allocate an instance on the cluster.
647
tryAlloc :: (Monad m) =>
648
            Node.List         -- ^ The node list
649
         -> Instance.List     -- ^ The instance list
650
         -> Instance.Instance -- ^ The instance to allocate
651
         -> AllocNodes        -- ^ The allocation targets
652
         -> m AllocSolution   -- ^ Possible solution list
653
tryAlloc nl _ inst (Right ok_pairs) =
654
    let sols = foldl' (\cstate (p, s) ->
655
                           concatAllocs cstate $ allocateOnPair nl inst p s
656
                      ) emptySolution ok_pairs
657

    
658
    in if null ok_pairs -- means we have just one node
659
       then fail "Not enough online nodes"
660
       else return $ annotateSolution sols
661

    
662
tryAlloc nl _ inst (Left all_nodes) =
663
    let sols = foldl' (\cstate ->
664
                           concatAllocs cstate . allocateOnSingle nl inst
665
                      ) emptySolution all_nodes
666
    in if null all_nodes
667
       then fail "No online nodes"
668
       else return $ annotateSolution sols
669

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

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

    
692
-- | Sort multigroup results based on policy and score
693
sortMGResults :: Group.List
694
             -> [(Gdx, AllocSolution)]
695
             -> [(Gdx, AllocSolution)]
696
sortMGResults gl sols =
697
    let extractScore = \(_, _, _, x) -> x
698
        solScore (gdx, sol) = (Group.allocPolicy (Container.find gdx gl),
699
                               (extractScore . head . asSolutions) sol)
700
    in sortBy (comparing solScore) sols
701

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

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

    
749
tryReloc _ _ _ reqn _  = fail $ "Unsupported number of relocation \
750
                                \destinations required (" ++ show reqn ++
751
                                                  "), only one supported"
752

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

    
771
-- | Change an instance's secondary node
772
evacInstance :: (Monad m) =>
773
                [Ndx]                      -- ^ Excluded nodes
774
             -> Instance.List              -- ^ The current instance list
775
             -> (Node.List, AllocSolution) -- ^ The current state
776
             -> Idx                        -- ^ The instance to evacuate
777
             -> m (Node.List, AllocSolution)
778
evacInstance ex_ndx il (nl, old_as) idx = do
779
  -- FIXME: hardcoded one node here
780

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

    
799
-- | Try to evacuate a list of nodes.
800
tryEvac :: (Monad m) =>
801
            Node.List       -- ^ The node list
802
         -> Instance.List   -- ^ The instance list
803
         -> [Idx]           -- ^ Instances to be evacuated
804
         -> [Ndx]           -- ^ Restricted nodes (the ones being evacuated)
805
         -> m AllocSolution -- ^ Solution list
806
tryEvac nl il idxs ex_ndx = do
807
  (_, sol) <- foldM (evacInstance ex_ndx il) (nl, emptySolution) idxs
808
  return sol
809

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

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

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

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

    
899
-- * Formatting functions
900

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

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

    
951
-- | Return the instance and involved nodes in an instance move.
952
involvedNodes :: Instance.List -> Placement -> [Ndx]
953
involvedNodes il plc =
954
    let (i, np, ns, _, _) = plc
955
        inst = Container.find i il
956
        op = Instance.pNode inst
957
        os = Instance.sNode inst
958
    in nub [np, ns, op, os]
959

    
960
-- | Inner function for splitJobs, that either appends the next job to
961
-- the current jobset, or starts a new jobset.
962
mergeJobs :: ([JobSet], [Ndx]) -> MoveJob -> ([JobSet], [Ndx])
963
mergeJobs ([], _) n@(ndx, _, _, _) = ([[n]], ndx)
964
mergeJobs (cjs@(j:js), nbuf) n@(ndx, _, _, _)
965
    | null (ndx `intersect` nbuf) = ((n:j):js, ndx ++ nbuf)
966
    | otherwise = ([n]:cjs, ndx)
967

    
968
-- | Break a list of moves into independent groups. Note that this
969
-- will reverse the order of jobs.
970
splitJobs :: [MoveJob] -> [JobSet]
971
splitJobs = fst . foldl mergeJobs ([], [])
972

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

    
985
-- | Given a list of commands, prefix them with @gnt-instance@ and
986
-- also beautify the display a little.
987
formatCmds :: [JobSet] -> String
988
formatCmds =
989
    unlines .
990
    concatMap (\(jsn, js) -> concatMap (formatJob jsn (length js))
991
                             (zip [1..] js)) .
992
    zip [1..]
993

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

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

    
1032
-- | Shows statistics for a given node list.
1033
printStats :: Node.List -> String
1034
printStats nl =
1035
    let dcvs = compDetailedCV nl
1036
        (weights, names) = unzip detailedCVInfo
1037
        hd = zip3 (weights ++ repeat 1) (names ++ repeat "unknown") dcvs
1038
        formatted = map (\(w, header, val) ->
1039
                             printf "%s=%.8f(x%.2f)" header val w::String) hd
1040
    in intercalate ", " formatted
1041

    
1042
-- | Convert a placement into a list of OpCodes (basically a job).
1043
iMoveToJob :: Node.List -> Instance.List
1044
          -> Idx -> IMove -> [OpCodes.OpCode]
1045
iMoveToJob nl il idx move =
1046
    let inst = Container.find idx il
1047
        iname = Instance.name inst
1048
        lookNode  = Just . Container.nameOf nl
1049
        opF = if Instance.running inst
1050
              then OpCodes.OpMigrateInstance iname True False
1051
              else OpCodes.OpFailoverInstance iname False
1052
        opR n = OpCodes.OpReplaceDisks iname (lookNode n)
1053
                OpCodes.ReplaceNewSecondary [] Nothing
1054
    in case move of
1055
         Failover -> [ opF ]
1056
         ReplacePrimary np -> [ opF, opR np, opF ]
1057
         ReplaceSecondary ns -> [ opR ns ]
1058
         ReplaceAndFailover np -> [ opR np, opF ]
1059
         FailoverAndReplace ns -> [ opF, opR ns ]
1060

    
1061
-- * Node group functions
1062

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

    
1078
-- | Computes the group of an instance per the primary node
1079
instancePriGroup :: Node.List -> Instance.Instance -> Gdx
1080
instancePriGroup nl i =
1081
  let pnode = Container.find (Instance.pNode i) nl
1082
  in  Node.group pnode
1083

    
1084
-- | Compute the list of badly allocated instances (split across node
1085
-- groups)
1086
findSplitInstances :: Node.List -> Instance.List -> [Instance.Instance]
1087
findSplitInstances nl il =
1088
  filter (not . isOk . instanceGroup nl) (Container.elems il)
1089

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