Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Node.hs @ 487e1962

History | View | Annotate | Download (20.2 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
  , 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
  , iPolicy  :: T.IPolicy -- ^ The instance policy (of the node's group)
128
  } deriving (Show, Read, Eq)
129

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

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

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

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

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

    
151
-- * Helper functions
152

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

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

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

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

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

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

    
184
-- * Initialization functions
185

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

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

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

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

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

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

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

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

    
257
-- | Sets the max cpu usage ratio. This will update the node's
258
-- ipolicy, losing sharing (but it should be a seldomly done operation).
259
setMcpu :: Node -> Double -> Node
260
setMcpu t val =
261
  let new_ipol = (iPolicy t) { T.iPolicyVcpuRatio = val }
262
  in t { hiCpu = mCpuTohiCpu val (tCpu t), iPolicy = new_ipol }
263

    
264
-- | Sets the policy.
265
setPolicy :: T.IPolicy -> Node -> Node
266
setPolicy pol node =
267
  node { iPolicy = pol
268
       , hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio pol) (tCpu node) }
269

    
270
-- | Computes the maximum reserved memory for peers from a peer map.
271
computeMaxRes :: P.PeerMap -> P.Elem
272
computeMaxRes = P.maxElem
273

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

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

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

    
310
-- * Update functions
311

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

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

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

    
370
-- | Adds a primary instance (basic version).
371
addPri :: Node -> Instance.Instance -> T.OpResult Node
372
addPri = addPriEx False
373

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

    
419
-- | Adds a secondary instance (basic version).
420
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
421
addSec = addSecEx False
422

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

    
457
-- * Stats functions
458

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

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

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

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

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

    
494
-- * Display functions
495

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

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

    
574
-- | String converter for the node list functionality.
575
list :: [String] -> Node -> [String]
576
list fields t = map (showField t) fields
577

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

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