Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Node.hs @ aa5b2f07

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

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

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

    
85
import qualified Ganeti.HTools.Types as T
86

    
87
-- * Type declarations
88

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

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

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

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

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

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

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

    
152
-- * Helper functions
153

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

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

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

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

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

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

    
185
-- * Initialization functions
186

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

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

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

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

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

    
247
-- | Sets the offline attribute.
248
setOffline :: Node -> Bool -> Node
249
setOffline t val = t { offline = val }
250

    
251
-- | Sets the unnaccounted memory.
252
setXmem :: Node -> Int -> Node
253
setXmem t val = t { xMem = val }
254

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

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

    
263
-- | Sets the policy.
264
setPolicy :: T.IPolicy -> Node -> Node
265
setPolicy pol node = node { iPolicy = pol }
266

    
267
-- | Computes the maximum reserved memory for peers from a peer map.
268
computeMaxRes :: P.PeerMap -> P.Elem
269
computeMaxRes = P.maxElem
270

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

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

    
298
-- | Assigns an instance to a node as secondary without other updates.
299
setSec :: Node -> Instance.Instance -> Node
300
setSec t inst = t { sList = Instance.idx inst:sList t
301
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
302
                                          T.dskWeight (Instance.util inst) }
303
                  }
304
  where old_load = utilLoad t
305

    
306
-- * Update functions
307

    
308
-- | Sets the free memory.
309
setFmem :: Node -> Int -> Node
310
setFmem t new_mem =
311
  let new_n1 = new_mem <= rMem t
312
      new_mp = fromIntegral new_mem / tMem t
313
  in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
314

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

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

    
366
-- | Adds a primary instance (basic version).
367
addPri :: Node -> Instance.Instance -> T.OpResult Node
368
addPri = addPriEx False
369

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

    
415
-- | Adds a secondary instance (basic version).
416
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
417
addSec = addSecEx False
418

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

    
454
-- * Stats functions
455

    
456
-- | Computes the amount of available disk on a given node.
457
availDisk :: Node -> Int
458
availDisk t =
459
  let _f = fDsk t
460
      _l = loDsk t
461
  in if _f < _l
462
       then 0
463
       else _f - _l
464

    
465
-- | Computes the amount of used disk on a given node.
466
iDsk :: Node -> Int
467
iDsk t = truncate (tDsk t) - fDsk t
468

    
469
-- | Computes the amount of available memory on a given node.
470
availMem :: Node -> Int
471
availMem t =
472
  let _f = fMem t
473
      _l = rMem t
474
  in if _f < _l
475
       then 0
476
       else _f - _l
477

    
478
-- | Computes the amount of available memory on a given node.
479
availCpu :: Node -> Int
480
availCpu t =
481
  let _u = uCpu t
482
      _l = hiCpu t
483
  in if _l >= _u
484
       then _l - _u
485
       else 0
486

    
487
-- | The memory used by instances on a given node.
488
iMem :: Node -> Int
489
iMem t = truncate (tMem t) - nMem t - xMem t - fMem t
490

    
491
-- * Display functions
492

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

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

    
571
-- | String converter for the node list functionality.
572
list :: [String] -> Node -> [String]
573
list fields t = map (showField t) fields
574

    
575
-- | Constant holding the fields we're displaying by default.
576
defaultFields :: [String]
577
defaultFields =
578
  [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
579
  , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
580
  , "pfmem", "pfdsk", "rcpu"
581
  , "cload", "mload", "dload", "nload" ]
582

    
583
-- | Split a list of nodes into a list of (node group UUID, list of
584
-- associated nodes).
585
computeGroups :: [Node] -> [(T.Gdx, [Node])]
586
computeGroups nodes =
587
  let nodes' = sortBy (comparing group) nodes
588
      nodes'' = groupBy (\a b -> group a == group b) nodes'
589
  in map (\nl -> (group (head nl), nl)) nodes''