Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Node.hs @ 74ff6aed

History | View | Annotate | Download (28.1 kB)

1
{-| Module describing a node.
2

    
3
    All updates are functional (copy-based) and return a new node with
4
    updated value.
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
10

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

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

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

    
26
-}
27

    
28
module Ganeti.HTools.Node
29
  ( Node(..)
30
  , List
31
  -- * Constructor
32
  , create
33
  -- ** Finalization after data loading
34
  , buildPeers
35
  , setIdx
36
  , setAlias
37
  , setOffline
38
  , setXmem
39
  , setFmem
40
  , setPri
41
  , setSec
42
  , setMaster
43
  , setNodeTags
44
  , setMdsk
45
  , setMcpu
46
  , setPolicy
47
  -- * Tag maps
48
  , addTags
49
  , delTags
50
  , rejectAddTags
51
  -- * Instance (re)location
52
  , removePri
53
  , removeSec
54
  , addPri
55
  , addPriEx
56
  , addSec
57
  , addSecEx
58
  -- * Stats
59
  , availDisk
60
  , availMem
61
  , availCpu
62
  , iMem
63
  , iDsk
64
  , conflictingPrimaries
65
  -- * Formatting
66
  , defaultFields
67
  , showHeader
68
  , showField
69
  , list
70
  -- * Misc stuff
71
  , AssocList
72
  , AllocElement
73
  , noSecondary
74
  , computeGroups
75
  , mkNodeGraph
76
  , mkRebootNodeGraph
77
  ) where
78

    
79
import Control.Monad (liftM, liftM2)
80
import Control.Applicative ((<$>), (<*>))
81
import qualified Data.Foldable as Foldable
82
import Data.Function (on)
83
import qualified Data.Graph as Graph
84
import qualified Data.IntMap as IntMap
85
import Data.List hiding (group)
86
import qualified Data.Map as Map
87
import Data.Ord (comparing)
88
import Text.Printf (printf)
89

    
90
import qualified Ganeti.HTools.Container as Container
91
import qualified Ganeti.HTools.Instance as Instance
92
import qualified Ganeti.HTools.PeerMap as P
93

    
94
import Ganeti.BasicTypes
95
import qualified Ganeti.HTools.Types as T
96

    
97
-- * Type declarations
98

    
99
-- | The tag map type.
100
type TagMap = Map.Map String Int
101

    
102
-- | The node type.
103
data Node = Node
104
  { name     :: String    -- ^ The node name
105
  , alias    :: String    -- ^ The shortened name (for display purposes)
106
  , tMem     :: Double    -- ^ Total memory (MiB)
107
  , nMem     :: Int       -- ^ Node memory (MiB)
108
  , fMem     :: Int       -- ^ Free memory (MiB)
109
  , xMem     :: Int       -- ^ Unaccounted memory (MiB)
110
  , tDsk     :: Double    -- ^ Total disk space (MiB)
111
  , fDsk     :: Int       -- ^ Free disk space (MiB)
112
  , tCpu     :: Double    -- ^ Total CPU count
113
  , uCpu     :: Int       -- ^ Used VCPU count
114
  , tSpindles :: Int      -- ^ Node spindles (spindle_count node parameter,
115
                          -- or actual spindles, see note below)
116
  , fSpindles :: Int      -- ^ Free spindles (see note below)
117
  , pList    :: [T.Idx]   -- ^ List of primary instance indices
118
  , sList    :: [T.Idx]   -- ^ List of secondary instance indices
119
  , idx      :: T.Ndx     -- ^ Internal index for book-keeping
120
  , peers    :: P.PeerMap -- ^ Pnode to instance mapping
121
  , failN1   :: Bool      -- ^ Whether the node has failed n1
122
  , rMem     :: Int       -- ^ Maximum memory needed for failover by
123
                          -- primaries of this node
124
  , pMem     :: Double    -- ^ Percent of free memory
125
  , pDsk     :: Double    -- ^ Percent of free disk
126
  , pRem     :: Double    -- ^ Percent of reserved memory
127
  , pCpu     :: Double    -- ^ Ratio of virtual to physical CPUs
128
  , mDsk     :: Double    -- ^ Minimum free disk ratio
129
  , loDsk    :: Int       -- ^ Autocomputed from mDsk low disk
130
                          -- threshold
131
  , hiCpu    :: Int       -- ^ Autocomputed from mCpu high cpu
132
                          -- threshold
133
  , hiSpindles :: Double  -- ^ Limit auto-computed from policy spindle_ratio
134
                          -- and the node spindle count (see note below)
135
  , instSpindles :: Double -- ^ Spindles used by instances (see note below)
136
  , offline  :: Bool      -- ^ Whether the node should not be used for
137
                          -- allocations and skipped from score
138
                          -- computations
139
  , isMaster :: Bool      -- ^ Whether the node is the master node
140
  , nTags    :: [String]  -- ^ The node tags for this node
141
  , utilPool :: T.DynUtil -- ^ Total utilisation capacity
142
  , utilLoad :: T.DynUtil -- ^ Sum of instance utilisation
143
  , pTags    :: TagMap    -- ^ Primary instance exclusion tags and their count
144
  , group    :: T.Gdx     -- ^ The node's group (index)
145
  , iPolicy  :: T.IPolicy -- ^ The instance policy (of the node's group)
146
  , exclStorage :: Bool   -- ^ Effective value of exclusive_storage
147
  } deriving (Show, Eq)
148
{- A note on how we handle spindles
149

    
150
With exclusive storage spindles is a resource, so we track the number of
151
spindles still available (fSpindles). This is the only reliable way, as some
152
spindles could be used outside of Ganeti. When exclusive storage is off,
153
spindles are a way to represent disk I/O pressure, and hence we track the amount
154
used by the instances. We compare it against 'hiSpindles', computed from the
155
instance policy, to avoid policy violations. In both cases we store the total
156
spindles in 'tSpindles'.
157
-}
158

    
159
instance T.Element Node where
160
  nameOf = name
161
  idxOf = idx
162
  setAlias = setAlias
163
  setIdx = setIdx
164
  allNames n = [name n, alias n]
165

    
166
-- | A simple name for the int, node association list.
167
type AssocList = [(T.Ndx, Node)]
168

    
169
-- | A simple name for a node map.
170
type List = Container.Container Node
171

    
172
-- | A simple name for an allocation element (here just for logistic
173
-- reasons).
174
type AllocElement = (List, Instance.Instance, [Node], T.Score)
175

    
176
-- | Constant node index for a non-moveable instance.
177
noSecondary :: T.Ndx
178
noSecondary = -1
179

    
180
-- * Helper functions
181

    
182
-- | Add a tag to a tagmap.
183
addTag :: TagMap -> String -> TagMap
184
addTag t s = Map.insertWith (+) s 1 t
185

    
186
-- | Add multiple tags.
187
addTags :: TagMap -> [String] -> TagMap
188
addTags = foldl' addTag
189

    
190
-- | Adjust or delete a tag from a tagmap.
191
delTag :: TagMap -> String -> TagMap
192
delTag t s = Map.update (\v -> if v > 1
193
                                 then Just (v-1)
194
                                 else Nothing)
195
             s t
196

    
197
-- | Remove multiple tags.
198
delTags :: TagMap -> [String] -> TagMap
199
delTags = foldl' delTag
200

    
201
-- | Check if we can add a list of tags to a tagmap.
202
rejectAddTags :: TagMap -> [String] -> Bool
203
rejectAddTags t = any (`Map.member` t)
204

    
205
-- | Check how many primary instances have conflicting tags. The
206
-- algorithm to compute this is to sum the count of all tags, then
207
-- subtract the size of the tag map (since each tag has at least one,
208
-- non-conflicting instance); this is equivalent to summing the
209
-- values in the tag map minus one.
210
conflictingPrimaries :: Node -> Int
211
conflictingPrimaries (Node { pTags = t }) = Foldable.sum t - Map.size t
212

    
213
-- | Helper function to increment a base value depending on the passed
214
-- boolean argument.
215
incIf :: (Num a) => Bool -> a -> a -> a
216
incIf True  base delta = base + delta
217
incIf False base _     = base
218

    
219
-- | Helper function to decrement a base value depending on the passed
220
-- boolean argument.
221
decIf :: (Num a) => Bool -> a -> a -> a
222
decIf True  base delta = base - delta
223
decIf False base _     = base
224

    
225
-- * Initialization functions
226

    
227
-- | Create a new node.
228
--
229
-- The index and the peers maps are empty, and will be need to be
230
-- update later via the 'setIdx' and 'buildPeers' functions.
231
create :: String -> Double -> Int -> Int -> Double
232
       -> Int -> Double -> Bool -> Int -> Int -> T.Gdx -> Bool -> Node
233
create name_init mem_t_init mem_n_init mem_f_init
234
       dsk_t_init dsk_f_init cpu_t_init offline_init spindles_t_init
235
       spindles_f_init group_init excl_stor =
236
  Node { name = name_init
237
       , alias = name_init
238
       , tMem = mem_t_init
239
       , nMem = mem_n_init
240
       , fMem = mem_f_init
241
       , tDsk = dsk_t_init
242
       , fDsk = dsk_f_init
243
       , tCpu = cpu_t_init
244
       , tSpindles = spindles_t_init
245
       , fSpindles = spindles_f_init
246
       , uCpu = 0
247
       , pList = []
248
       , sList = []
249
       , failN1 = True
250
       , idx = -1
251
       , peers = P.empty
252
       , rMem = 0
253
       , pMem = fromIntegral mem_f_init / mem_t_init
254
       , pDsk = computePDsk dsk_f_init dsk_t_init
255
       , pRem = 0
256
       , pCpu = 0
257
       , offline = offline_init
258
       , isMaster = False
259
       , nTags = []
260
       , xMem = 0
261
       , mDsk = T.defReservedDiskRatio
262
       , loDsk = mDskToloDsk T.defReservedDiskRatio dsk_t_init
263
       , hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio T.defIPolicy) cpu_t_init
264
       , hiSpindles = computeHiSpindles (T.iPolicySpindleRatio T.defIPolicy)
265
                      spindles_t_init
266
       , instSpindles = 0
267
       , utilPool = T.baseUtil
268
       , utilLoad = T.zeroUtil
269
       , pTags = Map.empty
270
       , group = group_init
271
       , iPolicy = T.defIPolicy
272
       , exclStorage = excl_stor
273
       }
274

    
275
-- | Conversion formula from mDsk\/tDsk to loDsk.
276
mDskToloDsk :: Double -> Double -> Int
277
mDskToloDsk mval = floor . (mval *)
278

    
279
-- | Conversion formula from mCpu\/tCpu to hiCpu.
280
mCpuTohiCpu :: Double -> Double -> Int
281
mCpuTohiCpu mval = floor . (mval *)
282

    
283
-- | Conversiojn formula from spindles and spindle ratio to hiSpindles.
284
computeHiSpindles :: Double -> Int -> Double
285
computeHiSpindles spindle_ratio = (spindle_ratio *) . fromIntegral
286

    
287
-- | Changes the index.
288
--
289
-- This is used only during the building of the data structures.
290
setIdx :: Node -> T.Ndx -> Node
291
setIdx t i = t {idx = i}
292

    
293
-- | Changes the alias.
294
--
295
-- This is used only during the building of the data structures.
296
setAlias :: Node -> String -> Node
297
setAlias t s = t { alias = s }
298

    
299
-- | Sets the offline attribute.
300
setOffline :: Node -> Bool -> Node
301
setOffline t val = t { offline = val }
302

    
303
-- | Sets the master attribute
304
setMaster :: Node -> Bool -> Node
305
setMaster t val = t { isMaster = val }
306

    
307
-- | Sets the node tags attribute
308
setNodeTags :: Node -> [String] -> Node
309
setNodeTags t val = t { nTags = val }
310

    
311
-- | Sets the unnaccounted memory.
312
setXmem :: Node -> Int -> Node
313
setXmem t val = t { xMem = val }
314

    
315
-- | Sets the max disk usage ratio.
316
setMdsk :: Node -> Double -> Node
317
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
318

    
319
-- | Sets the max cpu usage ratio. This will update the node's
320
-- ipolicy, losing sharing (but it should be a seldomly done operation).
321
setMcpu :: Node -> Double -> Node
322
setMcpu t val =
323
  let new_ipol = (iPolicy t) { T.iPolicyVcpuRatio = val }
324
  in t { hiCpu = mCpuTohiCpu val (tCpu t), iPolicy = new_ipol }
325

    
326
-- | Sets the policy.
327
setPolicy :: T.IPolicy -> Node -> Node
328
setPolicy pol node =
329
  node { iPolicy = pol
330
       , hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio pol) (tCpu node)
331
       , hiSpindles = computeHiSpindles (T.iPolicySpindleRatio pol)
332
                      (tSpindles node)
333
       }
334

    
335
-- | Computes the maximum reserved memory for peers from a peer map.
336
computeMaxRes :: P.PeerMap -> P.Elem
337
computeMaxRes = P.maxElem
338

    
339
-- | Builds the peer map for a given node.
340
buildPeers :: Node -> Instance.List -> Node
341
buildPeers t il =
342
  let mdata = map
343
              (\i_idx -> let inst = Container.find i_idx il
344
                             mem = if Instance.usesSecMem inst
345
                                     then Instance.mem inst
346
                                     else 0
347
                         in (Instance.pNode inst, mem))
348
              (sList t)
349
      pmap = P.accumArray (+) mdata
350
      new_rmem = computeMaxRes pmap
351
      new_failN1 = fMem t <= new_rmem
352
      new_prem = fromIntegral new_rmem / tMem t
353
  in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
354

    
355
-- | Calculate the new spindle usage
356
calcSpindleUse ::
357
                  Bool -- Action: True = adding instance, False = removing it
358
               -> Node -> Instance.Instance -> Double
359
calcSpindleUse _ (Node {exclStorage = True}) _ = 0.0
360
calcSpindleUse act n@(Node {exclStorage = False}) i =
361
  f (Instance.usesLocalStorage i) (instSpindles n)
362
    (fromIntegral $ Instance.spindleUse i)
363
    where
364
      f :: Bool -> Double -> Double -> Double -- avoid monomorphism restriction
365
      f = if act then incIf else decIf
366

    
367
-- | Calculate the new number of free spindles
368
calcNewFreeSpindles ::
369
                       Bool -- Action: True = adding instance, False = removing
370
                    -> Node -> Instance.Instance -> Int
371
calcNewFreeSpindles _ (Node {exclStorage = False}) _ = 0
372
calcNewFreeSpindles act n@(Node {exclStorage = True}) i =
373
  case Instance.getTotalSpindles i of
374
    Nothing -> if act
375
               then -1 -- Force a spindle error, so the instance don't go here
376
               else fSpindles n -- No change, as we aren't sure
377
    Just s -> (if act then (-) else (+)) (fSpindles n) s
378

    
379
-- | Assigns an instance to a node as primary and update the used VCPU
380
-- count, utilisation data and tags map.
381
setPri :: Node -> Instance.Instance -> Node
382
setPri t inst = t { pList = Instance.idx inst:pList t
383
                  , uCpu = new_count
384
                  , pCpu = fromIntegral new_count / tCpu t
385
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
386
                  , pTags = addTags (pTags t) (Instance.exclTags inst)
387
                  , instSpindles = calcSpindleUse True t inst
388
                  }
389
  where new_count = Instance.applyIfOnline inst (+ Instance.vcpus inst)
390
                    (uCpu t )
391

    
392
-- | Assigns an instance to a node as secondary and updates disk utilisation.
393
setSec :: Node -> Instance.Instance -> Node
394
setSec t inst = t { sList = Instance.idx inst:sList t
395
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
396
                                          T.dskWeight (Instance.util inst) }
397
                  , instSpindles = calcSpindleUse True t inst
398
                  }
399
  where old_load = utilLoad t
400

    
401
-- | Computes the new 'pDsk' value, handling nodes without local disk
402
-- storage (we consider all their disk used).
403
computePDsk :: Int -> Double -> Double
404
computePDsk _    0     = 1
405
computePDsk used total = fromIntegral used / total
406

    
407
-- * Update functions
408

    
409
-- | Sets the free memory.
410
setFmem :: Node -> Int -> Node
411
setFmem t new_mem =
412
  let new_n1 = new_mem < rMem t
413
      new_mp = fromIntegral new_mem / tMem t
414
  in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
415

    
416
-- | Removes a primary instance.
417
removePri :: Node -> Instance.Instance -> Node
418
removePri t inst =
419
  let iname = Instance.idx inst
420
      i_online = Instance.notOffline inst
421
      uses_disk = Instance.usesLocalStorage inst
422
      new_plist = delete iname (pList t)
423
      new_mem = incIf i_online (fMem t) (Instance.mem inst)
424
      new_dsk = incIf uses_disk (fDsk t) (Instance.dsk inst)
425
      new_free_sp = calcNewFreeSpindles False t inst
426
      new_inst_sp = calcSpindleUse False t inst
427
      new_mp = fromIntegral new_mem / tMem t
428
      new_dp = computePDsk new_dsk (tDsk t)
429
      new_failn1 = new_mem <= rMem t
430
      new_ucpu = decIf i_online (uCpu t) (Instance.vcpus inst)
431
      new_rcpu = fromIntegral new_ucpu / tCpu t
432
      new_load = utilLoad t `T.subUtil` Instance.util inst
433
  in t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
434
       , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
435
       , uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load
436
       , pTags = delTags (pTags t) (Instance.exclTags inst)
437
       , instSpindles = new_inst_sp, fSpindles = new_free_sp
438
       }
439

    
440
-- | Removes a secondary instance.
441
removeSec :: Node -> Instance.Instance -> Node
442
removeSec t inst =
443
  let iname = Instance.idx inst
444
      uses_disk = Instance.usesLocalStorage inst
445
      cur_dsk = fDsk t
446
      pnode = Instance.pNode inst
447
      new_slist = delete iname (sList t)
448
      new_dsk = incIf uses_disk cur_dsk (Instance.dsk inst)
449
      new_free_sp = calcNewFreeSpindles False t inst
450
      new_inst_sp = calcSpindleUse False t inst
451
      old_peers = peers t
452
      old_peem = P.find pnode old_peers
453
      new_peem = decIf (Instance.usesSecMem inst) old_peem (Instance.mem inst)
454
      new_peers = if new_peem > 0
455
                    then P.add pnode new_peem old_peers
456
                    else P.remove pnode old_peers
457
      old_rmem = rMem t
458
      new_rmem = if old_peem < old_rmem
459
                   then old_rmem
460
                   else computeMaxRes new_peers
461
      new_prem = fromIntegral new_rmem / tMem t
462
      new_failn1 = fMem t <= new_rmem
463
      new_dp = computePDsk new_dsk (tDsk t)
464
      old_load = utilLoad t
465
      new_load = old_load { T.dskWeight = T.dskWeight old_load -
466
                                          T.dskWeight (Instance.util inst) }
467
  in t { sList = new_slist, fDsk = new_dsk, peers = new_peers
468
       , failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
469
       , pRem = new_prem, utilLoad = new_load
470
       , instSpindles = new_inst_sp, fSpindles = new_free_sp
471
       }
472

    
473
-- | Adds a primary instance (basic version).
474
addPri :: Node -> Instance.Instance -> T.OpResult Node
475
addPri = addPriEx False
476

    
477
-- | Adds a primary instance (extended version).
478
addPriEx :: Bool               -- ^ Whether to override the N+1 and
479
                               -- other /soft/ checks, useful if we
480
                               -- come from a worse status
481
                               -- (e.g. offline)
482
         -> Node               -- ^ The target node
483
         -> Instance.Instance  -- ^ The instance to add
484
         -> T.OpResult Node    -- ^ The result of the operation,
485
                               -- either the new version of the node
486
                               -- or a failure mode
487
addPriEx force t inst =
488
  let iname = Instance.idx inst
489
      i_online = Instance.notOffline inst
490
      uses_disk = Instance.usesLocalStorage inst
491
      cur_dsk = fDsk t
492
      new_mem = decIf i_online (fMem t) (Instance.mem inst)
493
      new_dsk = decIf uses_disk cur_dsk (Instance.dsk inst)
494
      new_free_sp = calcNewFreeSpindles True t inst
495
      new_inst_sp = calcSpindleUse True t inst
496
      new_failn1 = new_mem <= rMem t
497
      new_ucpu = incIf i_online (uCpu t) (Instance.vcpus inst)
498
      new_pcpu = fromIntegral new_ucpu / tCpu t
499
      new_dp = computePDsk new_dsk (tDsk t)
500
      l_cpu = T.iPolicyVcpuRatio $ iPolicy t
501
      new_load = utilLoad t `T.addUtil` Instance.util inst
502
      inst_tags = Instance.exclTags inst
503
      old_tags = pTags t
504
      strict = not force
505
  in case () of
506
       _ | new_mem <= 0 -> Bad T.FailMem
507
         | uses_disk && new_dsk <= 0 -> Bad T.FailDisk
508
         | uses_disk && mDsk t > new_dp && strict -> Bad T.FailDisk
509
         | uses_disk && exclStorage t && new_free_sp < 0 -> Bad T.FailSpindles
510
         | uses_disk && new_inst_sp > hiSpindles t && strict -> Bad T.FailDisk
511
         | new_failn1 && not (failN1 t) && strict -> Bad T.FailMem
512
         | l_cpu >= 0 && l_cpu < new_pcpu && strict -> Bad T.FailCPU
513
         | rejectAddTags old_tags inst_tags -> Bad T.FailTags
514
         | otherwise ->
515
           let new_plist = iname:pList t
516
               new_mp = fromIntegral new_mem / tMem t
517
               r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
518
                     , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
519
                     , uCpu = new_ucpu, pCpu = new_pcpu
520
                     , utilLoad = new_load
521
                     , pTags = addTags old_tags inst_tags
522
                     , instSpindles = new_inst_sp
523
                     , fSpindles = new_free_sp
524
                     }
525
           in Ok r
526

    
527
-- | Adds a secondary instance (basic version).
528
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
529
addSec = addSecEx False
530

    
531
-- | Adds a secondary instance (extended version).
532
addSecEx :: Bool -> Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
533
addSecEx force t inst pdx =
534
  let iname = Instance.idx inst
535
      old_peers = peers t
536
      old_mem = fMem t
537
      new_dsk = fDsk t - Instance.dsk inst
538
      new_free_sp = calcNewFreeSpindles True t inst
539
      new_inst_sp = calcSpindleUse True t inst
540
      secondary_needed_mem = if Instance.usesSecMem inst
541
                               then Instance.mem inst
542
                               else 0
543
      new_peem = P.find pdx old_peers + secondary_needed_mem
544
      new_peers = P.add pdx new_peem old_peers
545
      new_rmem = max (rMem t) new_peem
546
      new_prem = fromIntegral new_rmem / tMem t
547
      new_failn1 = old_mem <= new_rmem
548
      new_dp = computePDsk new_dsk (tDsk t)
549
      old_load = utilLoad t
550
      new_load = old_load { T.dskWeight = T.dskWeight old_load +
551
                                          T.dskWeight (Instance.util inst) }
552
      strict = not force
553
  in case () of
554
       _ | not (Instance.hasSecondary inst) -> Bad T.FailDisk
555
         | new_dsk <= 0 -> Bad T.FailDisk
556
         | mDsk t > new_dp && strict -> Bad T.FailDisk
557
         | exclStorage t && new_free_sp < 0 -> Bad T.FailSpindles
558
         | new_inst_sp > hiSpindles t && strict -> Bad T.FailDisk
559
         | secondary_needed_mem >= old_mem && strict -> Bad T.FailMem
560
         | new_failn1 && not (failN1 t) && strict -> Bad T.FailMem
561
         | otherwise ->
562
           let new_slist = iname:sList t
563
               r = t { sList = new_slist, fDsk = new_dsk
564
                     , peers = new_peers, failN1 = new_failn1
565
                     , rMem = new_rmem, pDsk = new_dp
566
                     , pRem = new_prem, utilLoad = new_load
567
                     , instSpindles = new_inst_sp
568
                     , fSpindles = new_free_sp
569
                     }
570
           in Ok r
571

    
572
-- * Stats functions
573

    
574
-- | Computes the amount of available disk on a given node.
575
availDisk :: Node -> Int
576
availDisk t =
577
  let _f = fDsk t
578
      _l = loDsk t
579
  in if _f < _l
580
       then 0
581
       else _f - _l
582

    
583
-- | Computes the amount of used disk on a given node.
584
iDsk :: Node -> Int
585
iDsk t = truncate (tDsk t) - fDsk t
586

    
587
-- | Computes the amount of available memory on a given node.
588
availMem :: Node -> Int
589
availMem t =
590
  let _f = fMem t
591
      _l = rMem t
592
  in if _f < _l
593
       then 0
594
       else _f - _l
595

    
596
-- | Computes the amount of available memory on a given node.
597
availCpu :: Node -> Int
598
availCpu t =
599
  let _u = uCpu t
600
      _l = hiCpu t
601
  in if _l >= _u
602
       then _l - _u
603
       else 0
604

    
605
-- | The memory used by instances on a given node.
606
iMem :: Node -> Int
607
iMem t = truncate (tMem t) - nMem t - xMem t - fMem t
608

    
609
-- * Node graph functions
610
-- These functions do the transformations needed so that nodes can be
611
-- represented as a graph connected by the instances that are replicated
612
-- on them.
613

    
614
-- * Making of a Graph from a node/instance list
615

    
616
-- | Transform an instance into a list of edges on the node graph
617
instanceToEdges :: Instance.Instance -> [Graph.Edge]
618
instanceToEdges i
619
  | Instance.hasSecondary i = [(pnode,snode), (snode,pnode)]
620
  | otherwise = []
621
    where pnode = Instance.pNode i
622
          snode = Instance.sNode i
623

    
624
-- | Transform the list of instances into list of destination edges
625
instancesToEdges :: Instance.List -> [Graph.Edge]
626
instancesToEdges = concatMap instanceToEdges . Container.elems
627

    
628
-- | Transform the list of nodes into vertices bounds.
629
-- Returns Nothing is the list is empty.
630
nodesToBounds :: List -> Maybe Graph.Bounds
631
nodesToBounds nl = liftM2 (,) nmin nmax
632
    where nmin = fmap (fst . fst) (IntMap.minViewWithKey nl)
633
          nmax = fmap (fst . fst) (IntMap.maxViewWithKey nl)
634

    
635
-- | The clique of the primary nodes of the instances with a given secondary.
636
-- Return the full graph of those nodes that are primary node of at least one
637
-- instance that has the given node as secondary.
638
nodeToSharedSecondaryEdge :: Instance.List -> Node -> [Graph.Edge]
639
nodeToSharedSecondaryEdge il n = (,) <$> primaries <*> primaries
640
  where primaries = map (Instance.pNode . flip Container.find il) $ sList n
641

    
642

    
643
-- | Predicate of an edge having both vertices in a set of nodes.
644
filterValid :: List -> [Graph.Edge] -> [Graph.Edge]
645
filterValid nl  =  filter $ \(x,y) -> IntMap.member x nl && IntMap.member y nl
646

    
647
-- | Transform a Node + Instance list into a NodeGraph type.
648
-- Returns Nothing if the node list is empty.
649
mkNodeGraph :: List -> Instance.List -> Maybe Graph.Graph
650
mkNodeGraph nl il =
651
  liftM (`Graph.buildG` (filterValid nl . instancesToEdges $ il))
652
  (nodesToBounds nl)
653

    
654
-- | Transform a Nodes + Instances into a NodeGraph with all reboot exclusions.
655
-- This includes edges between nodes that are the primary nodes of instances
656
-- that have the same secondary node. Nodes not in the node list will not be
657
-- part of the graph, but they are still considered for the edges arising from
658
-- two instances having the same secondary node.
659
-- Return Nothing if the node list is empty.
660
mkRebootNodeGraph :: List -> List -> Instance.List -> Maybe Graph.Graph
661
mkRebootNodeGraph allnodes nl il =
662
  liftM (`Graph.buildG` filterValid nl edges) (nodesToBounds nl)
663
  where
664
    edges = instancesToEdges il `union`
665
            (Container.elems allnodes >>= nodeToSharedSecondaryEdge il) 
666

    
667
-- * Display functions
668

    
669
-- | Return a field for a given node.
670
showField :: Node   -- ^ Node which we're querying
671
          -> String -- ^ Field name
672
          -> String -- ^ Field value as string
673
showField t field =
674
  case field of
675
    "idx"  -> printf "%4d" $ idx t
676
    "name" -> alias t
677
    "fqdn" -> name t
678
    "status" -> case () of
679
                  _ | offline t -> "-"
680
                    | failN1 t -> "*"
681
                    | otherwise -> " "
682
    "tmem" -> printf "%5.0f" $ tMem t
683
    "nmem" -> printf "%5d" $ nMem t
684
    "xmem" -> printf "%5d" $ xMem t
685
    "fmem" -> printf "%5d" $ fMem t
686
    "imem" -> printf "%5d" $ iMem t
687
    "rmem" -> printf "%5d" $ rMem t
688
    "amem" -> printf "%5d" $ fMem t - rMem t
689
    "tdsk" -> printf "%5.0f" $ tDsk t / 1024
690
    "fdsk" -> printf "%5d" $ fDsk t `div` 1024
691
    "tcpu" -> printf "%4.0f" $ tCpu t
692
    "ucpu" -> printf "%4d" $ uCpu t
693
    "pcnt" -> printf "%3d" $ length (pList t)
694
    "scnt" -> printf "%3d" $ length (sList t)
695
    "plist" -> show $ pList t
696
    "slist" -> show $ sList t
697
    "pfmem" -> printf "%6.4f" $ pMem t
698
    "pfdsk" -> printf "%6.4f" $ pDsk t
699
    "rcpu"  -> printf "%5.2f" $ pCpu t
700
    "cload" -> printf "%5.3f" uC
701
    "mload" -> printf "%5.3f" uM
702
    "dload" -> printf "%5.3f" uD
703
    "nload" -> printf "%5.3f" uN
704
    "ptags" -> intercalate "," . map (uncurry (printf "%s=%d")) .
705
               Map.toList $ pTags t
706
    "peermap" -> show $ peers t
707
    "spindle_count" -> show $ tSpindles t
708
    "hi_spindles" -> show $ hiSpindles t
709
    "inst_spindles" -> show $ instSpindles t
710
    _ -> T.unknownField
711
  where
712
    T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
713
                T.dskWeight = uD, T.netWeight = uN } = utilLoad t
714

    
715
-- | Returns the header and numeric propery of a field.
716
showHeader :: String -> (String, Bool)
717
showHeader field =
718
  case field of
719
    "idx" -> ("Index", True)
720
    "name" -> ("Name", False)
721
    "fqdn" -> ("Name", False)
722
    "status" -> ("F", False)
723
    "tmem" -> ("t_mem", True)
724
    "nmem" -> ("n_mem", True)
725
    "xmem" -> ("x_mem", True)
726
    "fmem" -> ("f_mem", True)
727
    "imem" -> ("i_mem", True)
728
    "rmem" -> ("r_mem", True)
729
    "amem" -> ("a_mem", True)
730
    "tdsk" -> ("t_dsk", True)
731
    "fdsk" -> ("f_dsk", True)
732
    "tcpu" -> ("pcpu", True)
733
    "ucpu" -> ("vcpu", True)
734
    "pcnt" -> ("pcnt", True)
735
    "scnt" -> ("scnt", True)
736
    "plist" -> ("primaries", True)
737
    "slist" -> ("secondaries", True)
738
    "pfmem" -> ("p_fmem", True)
739
    "pfdsk" -> ("p_fdsk", True)
740
    "rcpu"  -> ("r_cpu", True)
741
    "cload" -> ("lCpu", True)
742
    "mload" -> ("lMem", True)
743
    "dload" -> ("lDsk", True)
744
    "nload" -> ("lNet", True)
745
    "ptags" -> ("PrimaryTags", False)
746
    "peermap" -> ("PeerMap", False)
747
    "spindle_count" -> ("NodeSpindles", True)
748
    "hi_spindles" -> ("MaxSpindles", True)
749
    "inst_spindles" -> ("InstSpindles", True)
750
    -- TODO: add node fields (group.uuid, group)
751
    _ -> (T.unknownField, False)
752

    
753
-- | String converter for the node list functionality.
754
list :: [String] -> Node -> [String]
755
list fields t = map (showField t) fields
756

    
757
-- | Constant holding the fields we're displaying by default.
758
defaultFields :: [String]
759
defaultFields =
760
  [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
761
  , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
762
  , "pfmem", "pfdsk", "rcpu"
763
  , "cload", "mload", "dload", "nload" ]
764

    
765
{-# ANN computeGroups "HLint: ignore Use alternative" #-}
766
-- | Split a list of nodes into a list of (node group UUID, list of
767
-- associated nodes).
768
computeGroups :: [Node] -> [(T.Gdx, [Node])]
769
computeGroups nodes =
770
  let nodes' = sortBy (comparing group) nodes
771
      nodes'' = groupBy ((==) `on` group) nodes'
772
  -- use of head here is OK, since groupBy returns non-empty lists; if
773
  -- you remove groupBy, also remove use of head
774
  in map (\nl -> (group (head nl), nl)) nodes''