Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Node.hs @ 8bc34c7b

History | View | Annotate | Download (20.9 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
  , spindleCount :: Int   -- ^ Node spindles (spindle_count node parameter)
105
  , pList    :: [T.Idx]   -- ^ List of primary instance indices
106
  , sList    :: [T.Idx]   -- ^ List of secondary instance indices
107
  , idx      :: T.Ndx     -- ^ Internal index for book-keeping
108
  , peers    :: P.PeerMap -- ^ Pnode to instance mapping
109
  , failN1   :: Bool      -- ^ Whether the node has failed n1
110
  , rMem     :: Int       -- ^ Maximum memory needed for failover by
111
                          -- primaries of this node
112
  , pMem     :: Double    -- ^ Percent of free memory
113
  , pDsk     :: Double    -- ^ Percent of free disk
114
  , pRem     :: Double    -- ^ Percent of reserved memory
115
  , pCpu     :: Double    -- ^ Ratio of virtual to physical CPUs
116
  , mDsk     :: Double    -- ^ Minimum free disk ratio
117
  , loDsk    :: Int       -- ^ Autocomputed from mDsk low disk
118
                          -- threshold
119
  , hiCpu    :: Int       -- ^ Autocomputed from mCpu high cpu
120
                          -- threshold
121
  , hiSpindles :: Double  -- ^ Auto-computed from policy spindle_ratio
122
                          -- and the node spindle count
123
  , instSpindles :: Double -- ^ Spindles used by instances
124
  , offline  :: Bool      -- ^ Whether the node should not be used for
125
                          -- allocations and skipped from score
126
                          -- computations
127
  , utilPool :: T.DynUtil -- ^ Total utilisation capacity
128
  , utilLoad :: T.DynUtil -- ^ Sum of instance utilisation
129
  , pTags    :: TagMap    -- ^ Map of primary instance tags and their count
130
  , group    :: T.Gdx     -- ^ The node's group (index)
131
  , iPolicy  :: T.IPolicy -- ^ The instance policy (of the node's group)
132
  } deriving (Show, Read, Eq)
133

    
134
instance T.Element Node where
135
  nameOf = name
136
  idxOf = idx
137
  setAlias = setAlias
138
  setIdx = setIdx
139
  allNames n = [name n, alias n]
140

    
141
-- | A simple name for the int, node association list.
142
type AssocList = [(T.Ndx, Node)]
143

    
144
-- | A simple name for a node map.
145
type List = Container.Container Node
146

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

    
151
-- | Constant node index for a non-moveable instance.
152
noSecondary :: T.Ndx
153
noSecondary = -1
154

    
155
-- * Helper functions
156

    
157
-- | Add a tag to a tagmap.
158
addTag :: TagMap -> String -> TagMap
159
addTag t s = Map.insertWith (+) s 1 t
160

    
161
-- | Add multiple tags.
162
addTags :: TagMap -> [String] -> TagMap
163
addTags = foldl' addTag
164

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

    
172
-- | Remove multiple tags.
173
delTags :: TagMap -> [String] -> TagMap
174
delTags = foldl' delTag
175

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

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

    
188
-- * Initialization functions
189

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

    
234
-- | Conversion formula from mDsk\/tDsk to loDsk.
235
mDskToloDsk :: Double -> Double -> Int
236
mDskToloDsk mval = floor . (mval *)
237

    
238
-- | Conversion formula from mCpu\/tCpu to hiCpu.
239
mCpuTohiCpu :: Double -> Double -> Int
240
mCpuTohiCpu mval = floor . (mval *)
241

    
242
-- | Conversiojn formula from spindles and spindle ratio to hiSpindles.
243
computeHiSpindles :: Double -> Int -> Double
244
computeHiSpindles spindle_ratio = (spindle_ratio *) . fromIntegral
245

    
246
-- | Changes the index.
247
--
248
-- This is used only during the building of the data structures.
249
setIdx :: Node -> T.Ndx -> Node
250
setIdx t i = t {idx = i}
251

    
252
-- | Changes the alias.
253
--
254
-- This is used only during the building of the data structures.
255
setAlias :: Node -> String -> Node
256
setAlias t s = t { alias = s }
257

    
258
-- | Sets the offline attribute.
259
setOffline :: Node -> Bool -> Node
260
setOffline t val = t { offline = val }
261

    
262
-- | Sets the unnaccounted memory.
263
setXmem :: Node -> Int -> Node
264
setXmem t val = t { xMem = val }
265

    
266
-- | Sets the max disk usage ratio.
267
setMdsk :: Node -> Double -> Node
268
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
269

    
270
-- | Sets the max cpu usage ratio. This will update the node's
271
-- ipolicy, losing sharing (but it should be a seldomly done operation).
272
setMcpu :: Node -> Double -> Node
273
setMcpu t val =
274
  let new_ipol = (iPolicy t) { T.iPolicyVcpuRatio = val }
275
  in t { hiCpu = mCpuTohiCpu val (tCpu t), iPolicy = new_ipol }
276

    
277
-- | Sets the policy.
278
setPolicy :: T.IPolicy -> Node -> Node
279
setPolicy pol node =
280
  node { iPolicy = pol
281
       , hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio pol) (tCpu node)
282
       , hiSpindles = computeHiSpindles (T.iPolicySpindleRatio pol)
283
                      (spindleCount node)
284
       }
285

    
286
-- | Computes the maximum reserved memory for peers from a peer map.
287
computeMaxRes :: P.PeerMap -> P.Elem
288
computeMaxRes = P.maxElem
289

    
290
-- | Builds the peer map for a given node.
291
buildPeers :: Node -> Instance.List -> Node
292
buildPeers t il =
293
  let mdata = map
294
              (\i_idx -> let inst = Container.find i_idx il
295
                             mem = if Instance.usesSecMem inst
296
                                     then Instance.mem inst
297
                                     else 0
298
                         in (Instance.pNode inst, mem))
299
              (sList t)
300
      pmap = P.accumArray (+) mdata
301
      new_rmem = computeMaxRes pmap
302
      new_failN1 = fMem t <= new_rmem
303
      new_prem = fromIntegral new_rmem / tMem t
304
  in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
305

    
306
-- | Assigns an instance to a node as primary and update the used VCPU
307
-- count, utilisation data and tags map.
308
setPri :: Node -> Instance.Instance -> Node
309
setPri t inst = t { pList = Instance.idx inst:pList t
310
                  , uCpu = new_count
311
                  , pCpu = fromIntegral new_count / tCpu t
312
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
313
                  , pTags = addTags (pTags t) (Instance.tags inst)
314
                  }
315
  where new_count = Instance.applyIfOnline inst (+ Instance.vcpus inst)
316
                    (uCpu t )
317

    
318
-- | Assigns an instance to a node as secondary without other updates.
319
setSec :: Node -> Instance.Instance -> Node
320
setSec t inst = t { sList = Instance.idx inst:sList t
321
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
322
                                          T.dskWeight (Instance.util inst) }
323
                  }
324
  where old_load = utilLoad t
325

    
326
-- * Update functions
327

    
328
-- | Sets the free memory.
329
setFmem :: Node -> Int -> Node
330
setFmem t new_mem =
331
  let new_n1 = new_mem <= rMem t
332
      new_mp = fromIntegral new_mem / tMem t
333
  in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
334

    
335
-- | Removes a primary instance.
336
removePri :: Node -> Instance.Instance -> Node
337
removePri t inst =
338
  let iname = Instance.idx inst
339
      new_plist = delete iname (pList t)
340
      new_mem = Instance.applyIfOnline inst (+ Instance.mem inst) (fMem t)
341
      new_dsk = fDsk t + Instance.dsk inst
342
      new_mp = fromIntegral new_mem / tMem t
343
      new_dp = fromIntegral new_dsk / tDsk t
344
      new_failn1 = new_mem <= rMem t
345
      new_ucpu = Instance.applyIfOnline inst
346
                 (\x -> x - Instance.vcpus inst) (uCpu t)
347
      new_rcpu = fromIntegral new_ucpu / tCpu t
348
      new_load = utilLoad t `T.subUtil` Instance.util inst
349
  in t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
350
       , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
351
       , uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load
352
       , pTags = delTags (pTags t) (Instance.tags inst) }
353

    
354
-- | Removes a secondary instance.
355
removeSec :: Node -> Instance.Instance -> Node
356
removeSec t inst =
357
  let iname = Instance.idx inst
358
      cur_dsk = fDsk t
359
      pnode = Instance.pNode inst
360
      new_slist = delete iname (sList t)
361
      new_dsk = if Instance.usesLocalStorage inst
362
                  then cur_dsk + Instance.dsk inst
363
                  else cur_dsk
364
      old_peers = peers t
365
      old_peem = P.find pnode old_peers
366
      new_peem =  if Instance.usesSecMem inst
367
                    then old_peem - Instance.mem inst
368
                    else old_peem
369
      new_peers = if new_peem > 0
370
                    then P.add pnode new_peem old_peers
371
                    else P.remove pnode old_peers
372
      old_rmem = rMem t
373
      new_rmem = if old_peem < old_rmem
374
                   then old_rmem
375
                   else computeMaxRes new_peers
376
      new_prem = fromIntegral new_rmem / tMem t
377
      new_failn1 = fMem t <= new_rmem
378
      new_dp = fromIntegral new_dsk / tDsk t
379
      old_load = utilLoad t
380
      new_load = old_load { T.dskWeight = T.dskWeight old_load -
381
                                          T.dskWeight (Instance.util inst) }
382
  in t { sList = new_slist, fDsk = new_dsk, peers = new_peers
383
       , failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
384
       , pRem = new_prem, utilLoad = new_load }
385

    
386
-- | Adds a primary instance (basic version).
387
addPri :: Node -> Instance.Instance -> T.OpResult Node
388
addPri = addPriEx False
389

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

    
435
-- | Adds a secondary instance (basic version).
436
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
437
addSec = addSecEx False
438

    
439
-- | Adds a secondary instance (extended version).
440
addSecEx :: Bool -> Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
441
addSecEx force t inst pdx =
442
  let iname = Instance.idx inst
443
      old_peers = peers t
444
      old_mem = fMem t
445
      new_dsk = fDsk t - Instance.dsk inst
446
      secondary_needed_mem = if Instance.usesSecMem inst
447
                               then Instance.mem inst
448
                               else 0
449
      new_peem = P.find pdx old_peers + secondary_needed_mem
450
      new_peers = P.add pdx new_peem old_peers
451
      new_rmem = max (rMem t) new_peem
452
      new_prem = fromIntegral new_rmem / tMem t
453
      new_failn1 = old_mem <= new_rmem
454
      new_dp = fromIntegral new_dsk / tDsk t
455
      old_load = utilLoad t
456
      new_load = old_load { T.dskWeight = T.dskWeight old_load +
457
                                          T.dskWeight (Instance.util inst) }
458
      strict = not force
459
  in case () of
460
       _ | not (Instance.hasSecondary inst) -> T.OpFail T.FailDisk
461
         | new_dsk <= 0 -> T.OpFail T.FailDisk
462
         | mDsk t > new_dp && strict -> T.OpFail T.FailDisk
463
         | secondary_needed_mem >= old_mem && strict -> T.OpFail T.FailMem
464
         | new_failn1 && not (failN1 t) && strict -> T.OpFail T.FailMem
465
         | otherwise ->
466
           let new_slist = iname:sList t
467
               r = t { sList = new_slist, fDsk = new_dsk
468
                     , peers = new_peers, failN1 = new_failn1
469
                     , rMem = new_rmem, pDsk = new_dp
470
                     , pRem = new_prem, utilLoad = new_load }
471
           in T.OpGood r
472

    
473
-- * Stats functions
474

    
475
-- | Computes the amount of available disk on a given node.
476
availDisk :: Node -> Int
477
availDisk t =
478
  let _f = fDsk t
479
      _l = loDsk t
480
  in if _f < _l
481
       then 0
482
       else _f - _l
483

    
484
-- | Computes the amount of used disk on a given node.
485
iDsk :: Node -> Int
486
iDsk t = truncate (tDsk t) - fDsk t
487

    
488
-- | Computes the amount of available memory on a given node.
489
availMem :: Node -> Int
490
availMem t =
491
  let _f = fMem t
492
      _l = rMem t
493
  in if _f < _l
494
       then 0
495
       else _f - _l
496

    
497
-- | Computes the amount of available memory on a given node.
498
availCpu :: Node -> Int
499
availCpu t =
500
  let _u = uCpu t
501
      _l = hiCpu t
502
  in if _l >= _u
503
       then _l - _u
504
       else 0
505

    
506
-- | The memory used by instances on a given node.
507
iMem :: Node -> Int
508
iMem t = truncate (tMem t) - nMem t - xMem t - fMem t
509

    
510
-- * Display functions
511

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

    
555
-- | Returns the header and numeric propery of a field.
556
showHeader :: String -> (String, Bool)
557
showHeader field =
558
  case field of
559
    "idx" -> ("Index", True)
560
    "name" -> ("Name", False)
561
    "fqdn" -> ("Name", False)
562
    "status" -> ("F", False)
563
    "tmem" -> ("t_mem", True)
564
    "nmem" -> ("n_mem", True)
565
    "xmem" -> ("x_mem", True)
566
    "fmem" -> ("f_mem", True)
567
    "imem" -> ("i_mem", True)
568
    "rmem" -> ("r_mem", True)
569
    "amem" -> ("a_mem", True)
570
    "tdsk" -> ("t_dsk", True)
571
    "fdsk" -> ("f_dsk", True)
572
    "tcpu" -> ("pcpu", True)
573
    "ucpu" -> ("vcpu", True)
574
    "pcnt" -> ("pcnt", True)
575
    "scnt" -> ("scnt", True)
576
    "plist" -> ("primaries", True)
577
    "slist" -> ("secondaries", True)
578
    "pfmem" -> ("p_fmem", True)
579
    "pfdsk" -> ("p_fdsk", True)
580
    "rcpu"  -> ("r_cpu", True)
581
    "cload" -> ("lCpu", True)
582
    "mload" -> ("lMem", True)
583
    "dload" -> ("lDsk", True)
584
    "nload" -> ("lNet", True)
585
    "ptags" -> ("PrimaryTags", False)
586
    "peermap" -> ("PeerMap", False)
587
    -- TODO: add node fields (group.uuid, group)
588
    _ -> (T.unknownField, False)
589

    
590
-- | String converter for the node list functionality.
591
list :: [String] -> Node -> [String]
592
list fields t = map (showField t) fields
593

    
594
-- | Constant holding the fields we're displaying by default.
595
defaultFields :: [String]
596
defaultFields =
597
  [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
598
  , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
599
  , "pfmem", "pfdsk", "rcpu"
600
  , "cload", "mload", "dload", "nload" ]
601

    
602
-- | Split a list of nodes into a list of (node group UUID, list of
603
-- associated nodes).
604
computeGroups :: [Node] -> [(T.Gdx, [Node])]
605
computeGroups nodes =
606
  let nodes' = sortBy (comparing group) nodes
607
      nodes'' = groupBy (\a b -> group a == group b) nodes'
608
  in map (\nl -> (group (head nl), nl)) nodes''