Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Node.hs @ 3603605a

History | View | Annotate | Download (19.8 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 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
  , setMdsk
43
  , setMcpu
44
  -- * Tag maps
45
  , addTags
46
  , delTags
47
  , rejectAddTags
48
  -- * Instance (re)location
49
  , removePri
50
  , removeSec
51
  , addPri
52
  , addPriEx
53
  , addSec
54
  , addSecEx
55
  -- * Stats
56
  , availDisk
57
  , availMem
58
  , availCpu
59
  , iMem
60
  , iDsk
61
  , conflictingPrimaries
62
  -- * Formatting
63
  , defaultFields
64
  , showHeader
65
  , showField
66
  , list
67
  -- * Misc stuff
68
  , AssocList
69
  , AllocElement
70
  , noSecondary
71
  , computeGroups
72
  ) where
73

    
74
import Data.List hiding (group)
75
import qualified Data.Map as Map
76
import qualified Data.Foldable as Foldable
77
import Data.Ord (comparing)
78
import Text.Printf (printf)
79

    
80
import qualified Ganeti.HTools.Container as Container
81
import qualified Ganeti.HTools.Instance as Instance
82
import qualified Ganeti.HTools.PeerMap as P
83

    
84
import qualified Ganeti.HTools.Types as T
85

    
86
-- * Type declarations
87

    
88
-- | The tag map type.
89
type TagMap = Map.Map String Int
90

    
91
-- | The node type.
92
data Node = Node
93
  { name     :: String    -- ^ The node name
94
  , alias    :: String    -- ^ The shortened name (for display purposes)
95
  , tMem     :: Double    -- ^ Total memory (MiB)
96
  , nMem     :: Int       -- ^ Node memory (MiB)
97
  , fMem     :: Int       -- ^ Free memory (MiB)
98
  , xMem     :: Int       -- ^ Unaccounted memory (MiB)
99
  , tDsk     :: Double    -- ^ Total disk space (MiB)
100
  , fDsk     :: Int       -- ^ Free disk space (MiB)
101
  , tCpu     :: Double    -- ^ Total CPU count
102
  , uCpu     :: Int       -- ^ Used VCPU count
103
  , pList    :: [T.Idx]   -- ^ List of primary instance indices
104
  , sList    :: [T.Idx]   -- ^ List of secondary instance indices
105
  , idx      :: T.Ndx     -- ^ Internal index for book-keeping
106
  , peers    :: P.PeerMap -- ^ Pnode to instance mapping
107
  , failN1   :: Bool      -- ^ Whether the node has failed n1
108
  , rMem     :: Int       -- ^ Maximum memory needed for failover by
109
                          -- primaries of this node
110
  , pMem     :: Double    -- ^ Percent of free memory
111
  , pDsk     :: Double    -- ^ Percent of free disk
112
  , pRem     :: Double    -- ^ Percent of reserved memory
113
  , pCpu     :: Double    -- ^ Ratio of virtual to physical CPUs
114
  , mDsk     :: Double    -- ^ Minimum free disk ratio
115
  , mCpu     :: Double    -- ^ Max ratio of virt-to-phys CPUs
116
  , loDsk    :: Int       -- ^ Autocomputed from mDsk low disk
117
                          -- threshold
118
  , hiCpu    :: Int       -- ^ Autocomputed from mCpu high cpu
119
                          -- threshold
120
  , offline  :: Bool      -- ^ Whether the node should not be used for
121
                          -- allocations and skipped from score
122
                          -- computations
123
  , utilPool :: T.DynUtil -- ^ Total utilisation capacity
124
  , utilLoad :: T.DynUtil -- ^ Sum of instance utilisation
125
  , pTags    :: TagMap    -- ^ Map of primary instance tags and their count
126
  , group    :: T.Gdx     -- ^ The node's group (index)
127
  } deriving (Show, Read, Eq)
128

    
129
instance T.Element Node where
130
  nameOf = name
131
  idxOf = idx
132
  setAlias = setAlias
133
  setIdx = setIdx
134
  allNames n = [name n, alias n]
135

    
136
-- | A simple name for the int, node association list.
137
type AssocList = [(T.Ndx, Node)]
138

    
139
-- | A simple name for a node map.
140
type List = Container.Container Node
141

    
142
-- | A simple name for an allocation element (here just for logistic
143
-- reasons).
144
type AllocElement = (List, Instance.Instance, [Node], T.Score)
145

    
146
-- | Constant node index for a non-moveable instance.
147
noSecondary :: T.Ndx
148
noSecondary = -1
149

    
150
-- * Helper functions
151

    
152
-- | Add a tag to a tagmap.
153
addTag :: TagMap -> String -> TagMap
154
addTag t s = Map.insertWith (+) s 1 t
155

    
156
-- | Add multiple tags.
157
addTags :: TagMap -> [String] -> TagMap
158
addTags = foldl' addTag
159

    
160
-- | Adjust or delete a tag from a tagmap.
161
delTag :: TagMap -> String -> TagMap
162
delTag t s = Map.update (\v -> if v > 1
163
                                 then Just (v-1)
164
                                 else Nothing)
165
             s t
166

    
167
-- | Remove multiple tags.
168
delTags :: TagMap -> [String] -> TagMap
169
delTags = foldl' delTag
170

    
171
-- | Check if we can add a list of tags to a tagmap.
172
rejectAddTags :: TagMap -> [String] -> Bool
173
rejectAddTags t = any (`Map.member` t)
174

    
175
-- | Check how many primary instances have conflicting tags. The
176
-- algorithm to compute this is to sum the count of all tags, then
177
-- subtract the size of the tag map (since each tag has at least one,
178
-- non-conflicting instance); this is equivalent to summing the
179
-- values in the tag map minus one.
180
conflictingPrimaries :: Node -> Int
181
conflictingPrimaries (Node { pTags = t }) = Foldable.sum t - Map.size t
182

    
183
-- * Initialization functions
184

    
185
-- | Create a new node.
186
--
187
-- The index and the peers maps are empty, and will be need to be
188
-- update later via the 'setIdx' and 'buildPeers' functions.
189
create :: String -> Double -> Int -> Int -> Double
190
       -> Int -> Double -> Bool -> T.Gdx -> Node
191
create name_init mem_t_init mem_n_init mem_f_init
192
       dsk_t_init dsk_f_init cpu_t_init offline_init group_init =
193
  Node { name = name_init
194
       , alias = name_init
195
       , tMem = mem_t_init
196
       , nMem = mem_n_init
197
       , fMem = mem_f_init
198
       , tDsk = dsk_t_init
199
       , fDsk = dsk_f_init
200
       , tCpu = cpu_t_init
201
       , uCpu = 0
202
       , pList = []
203
       , sList = []
204
       , failN1 = True
205
       , idx = -1
206
       , peers = P.empty
207
       , rMem = 0
208
       , pMem = fromIntegral mem_f_init / mem_t_init
209
       , pDsk = fromIntegral dsk_f_init / dsk_t_init
210
       , pRem = 0
211
       , pCpu = 0
212
       , offline = offline_init
213
       , xMem = 0
214
       , mDsk = T.defReservedDiskRatio
215
       , mCpu = T.defVcpuRatio
216
       , loDsk = mDskToloDsk T.defReservedDiskRatio dsk_t_init
217
       , hiCpu = mCpuTohiCpu T.defVcpuRatio cpu_t_init
218
       , utilPool = T.baseUtil
219
       , utilLoad = T.zeroUtil
220
       , pTags = Map.empty
221
       , group = group_init
222
       }
223

    
224
-- | Conversion formula from mDsk\/tDsk to loDsk.
225
mDskToloDsk :: Double -> Double -> Int
226
mDskToloDsk mval = floor . (mval *)
227

    
228
-- | Conversion formula from mCpu\/tCpu to hiCpu.
229
mCpuTohiCpu :: Double -> Double -> Int
230
mCpuTohiCpu mval = floor . (mval *)
231

    
232
-- | Changes the index.
233
--
234
-- This is used only during the building of the data structures.
235
setIdx :: Node -> T.Ndx -> Node
236
setIdx t i = t {idx = i}
237

    
238
-- | Changes the alias.
239
--
240
-- This is used only during the building of the data structures.
241
setAlias :: Node -> String -> Node
242
setAlias t s = t { alias = s }
243

    
244
-- | Sets the offline attribute.
245
setOffline :: Node -> Bool -> Node
246
setOffline t val = t { offline = val }
247

    
248
-- | Sets the unnaccounted memory.
249
setXmem :: Node -> Int -> Node
250
setXmem t val = t { xMem = val }
251

    
252
-- | Sets the max disk usage ratio.
253
setMdsk :: Node -> Double -> Node
254
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
255

    
256
-- | Sets the max cpu usage ratio.
257
setMcpu :: Node -> Double -> Node
258
setMcpu t val = t { mCpu = val, hiCpu = mCpuTohiCpu val (tCpu t) }
259

    
260
-- | Computes the maximum reserved memory for peers from a peer map.
261
computeMaxRes :: P.PeerMap -> P.Elem
262
computeMaxRes = P.maxElem
263

    
264
-- | Builds the peer map for a given node.
265
buildPeers :: Node -> Instance.List -> Node
266
buildPeers t il =
267
  let mdata = map
268
              (\i_idx -> let inst = Container.find i_idx il
269
                             mem = if Instance.autoBalance inst
270
                                     then Instance.mem inst
271
                                     else 0
272
                         in (Instance.pNode inst, mem))
273
              (sList t)
274
      pmap = P.accumArray (+) mdata
275
      new_rmem = computeMaxRes pmap
276
      new_failN1 = fMem t <= new_rmem
277
      new_prem = fromIntegral new_rmem / tMem t
278
  in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
279

    
280
-- | Assigns an instance to a node as primary and update the used VCPU
281
-- count, utilisation data and tags map.
282
setPri :: Node -> Instance.Instance -> Node
283
setPri t inst = t { pList = Instance.idx inst:pList t
284
                  , uCpu = new_count
285
                  , pCpu = fromIntegral new_count / tCpu t
286
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
287
                  , pTags = addTags (pTags t) (Instance.tags inst)
288
                  }
289
  where new_count = uCpu t + Instance.vcpus inst
290

    
291
-- | Assigns an instance to a node as secondary without other updates.
292
setSec :: Node -> Instance.Instance -> Node
293
setSec t inst = t { sList = Instance.idx inst:sList t
294
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
295
                                          T.dskWeight (Instance.util inst) }
296
                  }
297
  where old_load = utilLoad t
298

    
299
-- * Update functions
300

    
301
-- | Sets the free memory.
302
setFmem :: Node -> Int -> Node
303
setFmem t new_mem =
304
  let new_n1 = new_mem <= rMem t
305
      new_mp = fromIntegral new_mem / tMem t
306
  in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
307

    
308
-- | Removes a primary instance.
309
removePri :: Node -> Instance.Instance -> Node
310
removePri t inst =
311
  let iname = Instance.idx inst
312
      new_plist = delete iname (pList t)
313
      new_mem = Instance.applyIfOnline inst (+ Instance.mem inst) (fMem t)
314
      new_dsk = fDsk t + Instance.dsk inst
315
      new_mp = fromIntegral new_mem / tMem t
316
      new_dp = fromIntegral new_dsk / tDsk t
317
      new_failn1 = new_mem <= rMem t
318
      new_ucpu = Instance.applyIfOnline inst
319
                 (\x -> x - Instance.vcpus inst) (uCpu t)
320
      new_rcpu = fromIntegral new_ucpu / tCpu t
321
      new_load = utilLoad t `T.subUtil` Instance.util inst
322
  in t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
323
       , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
324
       , uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load
325
       , pTags = delTags (pTags t) (Instance.tags inst) }
326

    
327
-- | Removes a secondary instance.
328
removeSec :: Node -> Instance.Instance -> Node
329
removeSec t inst =
330
  let iname = Instance.idx inst
331
      cur_dsk = fDsk t
332
      pnode = Instance.pNode inst
333
      new_slist = delete iname (sList t)
334
      new_dsk = if Instance.usesLocalStorage inst
335
                  then cur_dsk + Instance.dsk inst
336
                  else cur_dsk
337
      old_peers = peers t
338
      old_peem = P.find pnode old_peers
339
      new_peem =  if Instance.autoBalance inst
340
                    then old_peem - Instance.mem inst
341
                    else old_peem
342
      new_peers = if new_peem > 0
343
                    then P.add pnode new_peem old_peers
344
                    else P.remove pnode old_peers
345
      old_rmem = rMem t
346
      new_rmem = if old_peem < old_rmem
347
                   then old_rmem
348
                   else computeMaxRes new_peers
349
      new_prem = fromIntegral new_rmem / tMem t
350
      new_failn1 = fMem t <= new_rmem
351
      new_dp = fromIntegral new_dsk / tDsk t
352
      old_load = utilLoad t
353
      new_load = old_load { T.dskWeight = T.dskWeight old_load -
354
                                          T.dskWeight (Instance.util inst) }
355
  in t { sList = new_slist, fDsk = new_dsk, peers = new_peers
356
       , failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
357
       , pRem = new_prem, utilLoad = new_load }
358

    
359
-- | Adds a primary instance (basic version).
360
addPri :: Node -> Instance.Instance -> T.OpResult Node
361
addPri = addPriEx False
362

    
363
-- | Adds a primary instance (extended version).
364
addPriEx :: Bool               -- ^ Whether to override the N+1 and
365
                               -- other /soft/ checks, useful if we
366
                               -- come from a worse status
367
                               -- (e.g. offline)
368
         -> Node               -- ^ The target node
369
         -> Instance.Instance  -- ^ The instance to add
370
         -> T.OpResult Node    -- ^ The result of the operation,
371
                               -- either the new version of the node
372
                               -- or a failure mode
373
addPriEx force t inst =
374
  let iname = Instance.idx inst
375
      uses_disk = Instance.usesLocalStorage inst
376
      cur_dsk = fDsk t
377
      new_mem = Instance.applyIfOnline inst
378
                (\x -> x - Instance.mem inst) (fMem t)
379
      new_dsk = if uses_disk
380
                  then cur_dsk - Instance.dsk inst
381
                  else cur_dsk
382
      new_failn1 = new_mem <= rMem t
383
      new_ucpu = Instance.applyIfOnline inst (+ Instance.vcpus inst) (uCpu t)
384
      new_pcpu = fromIntegral new_ucpu / tCpu t
385
      new_dp = fromIntegral new_dsk / tDsk t
386
      l_cpu = mCpu t
387
      new_load = utilLoad t `T.addUtil` Instance.util inst
388
      inst_tags = Instance.tags inst
389
      old_tags = pTags t
390
      strict = not force
391
  in case () of
392
       _ | new_mem <= 0 -> T.OpFail T.FailMem
393
         | uses_disk && new_dsk <= 0 -> T.OpFail T.FailDisk
394
         | uses_disk && mDsk t > new_dp && strict -> T.OpFail T.FailDisk
395
         | new_failn1 && not (failN1 t) && strict -> T.OpFail T.FailMem
396
         | l_cpu >= 0 && l_cpu < new_pcpu && strict -> T.OpFail T.FailCPU
397
         | rejectAddTags old_tags inst_tags -> T.OpFail T.FailTags
398
         | otherwise ->
399
           let new_plist = iname:pList t
400
               new_mp = fromIntegral new_mem / tMem t
401
               r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
402
                     , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
403
                     , uCpu = new_ucpu, pCpu = new_pcpu
404
                     , utilLoad = new_load
405
                     , pTags = addTags old_tags inst_tags }
406
           in T.OpGood r
407

    
408
-- | Adds a secondary instance (basic version).
409
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
410
addSec = addSecEx False
411

    
412
-- | Adds a secondary instance (extended version).
413
addSecEx :: Bool -> Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
414
addSecEx force t inst pdx =
415
  let iname = Instance.idx inst
416
      old_peers = peers t
417
      old_mem = fMem t
418
      new_dsk = fDsk t - Instance.dsk inst
419
      secondary_needed_mem = if Instance.autoBalance inst &&
420
                             not (Instance.instanceOffline inst)
421
                               then Instance.mem inst
422
                               else 0
423
      new_peem = P.find pdx old_peers + secondary_needed_mem
424
      new_peers = P.add pdx new_peem old_peers
425
      new_rmem = max (rMem t) new_peem
426
      new_prem = fromIntegral new_rmem / tMem t
427
      new_failn1 = old_mem <= new_rmem
428
      new_dp = fromIntegral new_dsk / tDsk t
429
      old_load = utilLoad t
430
      new_load = old_load { T.dskWeight = T.dskWeight old_load +
431
                                          T.dskWeight (Instance.util inst) }
432
      strict = not force
433
  in case () of
434
       _ | not (Instance.hasSecondary inst) -> T.OpFail T.FailDisk
435
         | new_dsk <= 0 -> T.OpFail T.FailDisk
436
         | mDsk t > new_dp && strict -> T.OpFail T.FailDisk
437
         | secondary_needed_mem >= old_mem && strict -> T.OpFail T.FailMem
438
         | new_failn1 && not (failN1 t) && strict -> T.OpFail T.FailMem
439
         | otherwise ->
440
           let new_slist = iname:sList t
441
               r = t { sList = new_slist, fDsk = new_dsk
442
                     , peers = new_peers, failN1 = new_failn1
443
                     , rMem = new_rmem, pDsk = new_dp
444
                     , pRem = new_prem, utilLoad = new_load }
445
           in T.OpGood r
446

    
447
-- * Stats functions
448

    
449
-- | Computes the amount of available disk on a given node.
450
availDisk :: Node -> Int
451
availDisk t =
452
  let _f = fDsk t
453
      _l = loDsk t
454
  in if _f < _l
455
       then 0
456
       else _f - _l
457

    
458
-- | Computes the amount of used disk on a given node.
459
iDsk :: Node -> Int
460
iDsk t = truncate (tDsk t) - fDsk t
461

    
462
-- | Computes the amount of available memory on a given node.
463
availMem :: Node -> Int
464
availMem t =
465
  let _f = fMem t
466
      _l = rMem t
467
  in if _f < _l
468
       then 0
469
       else _f - _l
470

    
471
-- | Computes the amount of available memory on a given node.
472
availCpu :: Node -> Int
473
availCpu t =
474
  let _u = uCpu t
475
      _l = hiCpu t
476
  in if _l >= _u
477
       then _l - _u
478
       else 0
479

    
480
-- | The memory used by instances on a given node.
481
iMem :: Node -> Int
482
iMem t = truncate (tMem t) - nMem t - xMem t - fMem t
483

    
484
-- * Display functions
485

    
486
-- | Return a field for a given node.
487
showField :: Node   -- ^ Node which we're querying
488
          -> String -- ^ Field name
489
          -> String -- ^ Field value as string
490
showField t field =
491
  case field of
492
    "idx"  -> printf "%4d" $ idx t
493
    "name" -> alias t
494
    "fqdn" -> name t
495
    "status" -> case () of
496
                  _ | offline t -> "-"
497
                    | failN1 t -> "*"
498
                    | otherwise -> " "
499
    "tmem" -> printf "%5.0f" $ tMem t
500
    "nmem" -> printf "%5d" $ nMem t
501
    "xmem" -> printf "%5d" $ xMem t
502
    "fmem" -> printf "%5d" $ fMem t
503
    "imem" -> printf "%5d" $ iMem t
504
    "rmem" -> printf "%5d" $ rMem t
505
    "amem" -> printf "%5d" $ fMem t - rMem t
506
    "tdsk" -> printf "%5.0f" $ tDsk t / 1024
507
    "fdsk" -> printf "%5d" $ fDsk t `div` 1024
508
    "tcpu" -> printf "%4.0f" $ tCpu t
509
    "ucpu" -> printf "%4d" $ uCpu t
510
    "pcnt" -> printf "%3d" $ length (pList t)
511
    "scnt" -> printf "%3d" $ length (sList t)
512
    "plist" -> show $ pList t
513
    "slist" -> show $ sList t
514
    "pfmem" -> printf "%6.4f" $ pMem t
515
    "pfdsk" -> printf "%6.4f" $ pDsk t
516
    "rcpu"  -> printf "%5.2f" $ pCpu t
517
    "cload" -> printf "%5.3f" uC
518
    "mload" -> printf "%5.3f" uM
519
    "dload" -> printf "%5.3f" uD
520
    "nload" -> printf "%5.3f" uN
521
    "ptags" -> intercalate "," . map (uncurry (printf "%s=%d")) .
522
               Map.toList $ pTags t
523
    "peermap" -> show $ peers t
524
    _ -> T.unknownField
525
  where
526
    T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
527
                T.dskWeight = uD, T.netWeight = uN } = utilLoad t
528

    
529
-- | Returns the header and numeric propery of a field.
530
showHeader :: String -> (String, Bool)
531
showHeader field =
532
  case field of
533
    "idx" -> ("Index", True)
534
    "name" -> ("Name", False)
535
    "fqdn" -> ("Name", False)
536
    "status" -> ("F", False)
537
    "tmem" -> ("t_mem", True)
538
    "nmem" -> ("n_mem", True)
539
    "xmem" -> ("x_mem", True)
540
    "fmem" -> ("f_mem", True)
541
    "imem" -> ("i_mem", True)
542
    "rmem" -> ("r_mem", True)
543
    "amem" -> ("a_mem", True)
544
    "tdsk" -> ("t_dsk", True)
545
    "fdsk" -> ("f_dsk", True)
546
    "tcpu" -> ("pcpu", True)
547
    "ucpu" -> ("vcpu", True)
548
    "pcnt" -> ("pcnt", True)
549
    "scnt" -> ("scnt", True)
550
    "plist" -> ("primaries", True)
551
    "slist" -> ("secondaries", True)
552
    "pfmem" -> ("p_fmem", True)
553
    "pfdsk" -> ("p_fdsk", True)
554
    "rcpu"  -> ("r_cpu", True)
555
    "cload" -> ("lCpu", True)
556
    "mload" -> ("lMem", True)
557
    "dload" -> ("lDsk", True)
558
    "nload" -> ("lNet", True)
559
    "ptags" -> ("PrimaryTags", False)
560
    "peermap" -> ("PeerMap", False)
561
    -- TODO: add node fields (group.uuid, group)
562
    _ -> (T.unknownField, False)
563

    
564
-- | String converter for the node list functionality.
565
list :: [String] -> Node -> [String]
566
list fields t = map (showField t) fields
567

    
568
-- | Constant holding the fields we're displaying by default.
569
defaultFields :: [String]
570
defaultFields =
571
  [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
572
  , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
573
  , "pfmem", "pfdsk", "rcpu"
574
  , "cload", "mload", "dload", "nload" ]
575

    
576
-- | Split a list of nodes into a list of (node group UUID, list of
577
-- associated nodes).
578
computeGroups :: [Node] -> [(T.Gdx, [Node])]
579
computeGroups nodes =
580
  let nodes' = sortBy (comparing group) nodes
581
      nodes'' = groupBy (\a b -> group a == group b) nodes'
582
  in map (\nl -> (group (head nl), nl)) nodes''