Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Node.hs @ 4c18f468

History | View | Annotate | Download (22.7 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
-- | Helper function to increment a base value depending on the passed
189
-- boolean argument.
190
incIf :: (Num a) => Bool -> a -> a -> a
191
incIf True  base delta = base + delta
192
incIf False base _     = base
193

    
194
-- | Helper function to decrement a base value depending on the passed
195
-- boolean argument.
196
decIf :: (Num a) => Bool -> a -> a -> a
197
decIf True  base delta = base - delta
198
decIf False base _     = base
199

    
200
-- * Initialization functions
201

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

    
246
-- | Conversion formula from mDsk\/tDsk to loDsk.
247
mDskToloDsk :: Double -> Double -> Int
248
mDskToloDsk mval = floor . (mval *)
249

    
250
-- | Conversion formula from mCpu\/tCpu to hiCpu.
251
mCpuTohiCpu :: Double -> Double -> Int
252
mCpuTohiCpu mval = floor . (mval *)
253

    
254
-- | Conversiojn formula from spindles and spindle ratio to hiSpindles.
255
computeHiSpindles :: Double -> Int -> Double
256
computeHiSpindles spindle_ratio = (spindle_ratio *) . fromIntegral
257

    
258
-- | Changes the index.
259
--
260
-- This is used only during the building of the data structures.
261
setIdx :: Node -> T.Ndx -> Node
262
setIdx t i = t {idx = i}
263

    
264
-- | Changes the alias.
265
--
266
-- This is used only during the building of the data structures.
267
setAlias :: Node -> String -> Node
268
setAlias t s = t { alias = s }
269

    
270
-- | Sets the offline attribute.
271
setOffline :: Node -> Bool -> Node
272
setOffline t val = t { offline = val }
273

    
274
-- | Sets the unnaccounted memory.
275
setXmem :: Node -> Int -> Node
276
setXmem t val = t { xMem = val }
277

    
278
-- | Sets the max disk usage ratio.
279
setMdsk :: Node -> Double -> Node
280
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
281

    
282
-- | Sets the max cpu usage ratio. This will update the node's
283
-- ipolicy, losing sharing (but it should be a seldomly done operation).
284
setMcpu :: Node -> Double -> Node
285
setMcpu t val =
286
  let new_ipol = (iPolicy t) { T.iPolicyVcpuRatio = val }
287
  in t { hiCpu = mCpuTohiCpu val (tCpu t), iPolicy = new_ipol }
288

    
289
-- | Sets the policy.
290
setPolicy :: T.IPolicy -> Node -> Node
291
setPolicy pol node =
292
  node { iPolicy = pol
293
       , hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio pol) (tCpu node)
294
       , hiSpindles = computeHiSpindles (T.iPolicySpindleRatio pol)
295
                      (spindleCount node)
296
       }
297

    
298
-- | Computes the maximum reserved memory for peers from a peer map.
299
computeMaxRes :: P.PeerMap -> P.Elem
300
computeMaxRes = P.maxElem
301

    
302
-- | Builds the peer map for a given node.
303
buildPeers :: Node -> Instance.List -> Node
304
buildPeers t il =
305
  let mdata = map
306
              (\i_idx -> let inst = Container.find i_idx il
307
                             mem = if Instance.usesSecMem inst
308
                                     then Instance.mem inst
309
                                     else 0
310
                         in (Instance.pNode inst, mem))
311
              (sList t)
312
      pmap = P.accumArray (+) mdata
313
      new_rmem = computeMaxRes pmap
314
      new_failN1 = fMem t <= new_rmem
315
      new_prem = fromIntegral new_rmem / tMem t
316
  in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
317

    
318
-- | Calculate the new spindle usage
319
calcSpindleUsage :: Node -> Instance.Instance -> Double
320
calcSpindleUsage n i = incIf (Instance.usesLocalStorage i) (instSpindles n)
321
                         (fromIntegral $ Instance.spindleUsage i)
322

    
323
-- | Assigns an instance to a node as primary and update the used VCPU
324
-- count, utilisation data and tags map.
325
setPri :: Node -> Instance.Instance -> Node
326
setPri t inst = t { pList = Instance.idx inst:pList t
327
                  , uCpu = new_count
328
                  , pCpu = fromIntegral new_count / tCpu t
329
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
330
                  , pTags = addTags (pTags t) (Instance.tags inst)
331
                  , instSpindles = calcSpindleUsage t inst
332
                  }
333
  where new_count = Instance.applyIfOnline inst (+ Instance.vcpus inst)
334
                    (uCpu t )
335

    
336
-- | Assigns an instance to a node as secondary without other updates.
337
setSec :: Node -> Instance.Instance -> Node
338
setSec t inst = t { sList = Instance.idx inst:sList t
339
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
340
                                          T.dskWeight (Instance.util inst) }
341
                  , instSpindles = calcSpindleUsage t inst
342
                  }
343
  where old_load = utilLoad t
344

    
345
-- | Computes the new 'pDsk' value, handling nodes without local disk
346
-- storage (we consider all their disk used).
347
computePDsk :: Int -> Double -> Double
348
computePDsk _    0     = 1
349
computePDsk used total = fromIntegral used / total
350

    
351
-- * Update functions
352

    
353
-- | Sets the free memory.
354
setFmem :: Node -> Int -> Node
355
setFmem t new_mem =
356
  let new_n1 = new_mem <= rMem t
357
      new_mp = fromIntegral new_mem / tMem t
358
  in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
359

    
360
-- | Removes a primary instance.
361
removePri :: Node -> Instance.Instance -> Node
362
removePri t inst =
363
  let iname = Instance.idx inst
364
      i_online = Instance.notOffline inst
365
      uses_disk = Instance.usesLocalStorage inst
366
      new_plist = delete iname (pList t)
367
      new_mem = incIf i_online (fMem t) (Instance.mem inst)
368
      new_dsk = incIf uses_disk (fDsk t) (Instance.dsk inst)
369
      new_spindles = decIf uses_disk (instSpindles t) 1
370
      new_mp = fromIntegral new_mem / tMem t
371
      new_dp = computePDsk new_dsk (tDsk t)
372
      new_failn1 = new_mem <= rMem t
373
      new_ucpu = decIf i_online (uCpu t) (Instance.vcpus inst)
374
      new_rcpu = fromIntegral new_ucpu / tCpu t
375
      new_load = utilLoad t `T.subUtil` Instance.util inst
376
  in t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
377
       , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
378
       , uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load
379
       , pTags = delTags (pTags t) (Instance.tags inst)
380
       , instSpindles = new_spindles
381
       }
382

    
383
-- | Removes a secondary instance.
384
removeSec :: Node -> Instance.Instance -> Node
385
removeSec t inst =
386
  let iname = Instance.idx inst
387
      uses_disk = Instance.usesLocalStorage inst
388
      cur_dsk = fDsk t
389
      pnode = Instance.pNode inst
390
      new_slist = delete iname (sList t)
391
      new_dsk = incIf uses_disk cur_dsk (Instance.dsk inst)
392
      new_spindles = decIf uses_disk (instSpindles t) 1
393
      old_peers = peers t
394
      old_peem = P.find pnode old_peers
395
      new_peem = decIf (Instance.usesSecMem inst) old_peem (Instance.mem inst)
396
      new_peers = if new_peem > 0
397
                    then P.add pnode new_peem old_peers
398
                    else P.remove pnode old_peers
399
      old_rmem = rMem t
400
      new_rmem = if old_peem < old_rmem
401
                   then old_rmem
402
                   else computeMaxRes new_peers
403
      new_prem = fromIntegral new_rmem / tMem t
404
      new_failn1 = fMem t <= new_rmem
405
      new_dp = computePDsk new_dsk (tDsk t)
406
      old_load = utilLoad t
407
      new_load = old_load { T.dskWeight = T.dskWeight old_load -
408
                                          T.dskWeight (Instance.util inst) }
409
  in t { sList = new_slist, fDsk = new_dsk, peers = new_peers
410
       , failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
411
       , pRem = new_prem, utilLoad = new_load
412
       , instSpindles = new_spindles
413
       }
414

    
415
-- | Adds a primary instance (basic version).
416
addPri :: Node -> Instance.Instance -> T.OpResult Node
417
addPri = addPriEx False
418

    
419
-- | Adds a primary instance (extended version).
420
addPriEx :: Bool               -- ^ Whether to override the N+1 and
421
                               -- other /soft/ checks, useful if we
422
                               -- come from a worse status
423
                               -- (e.g. offline)
424
         -> Node               -- ^ The target node
425
         -> Instance.Instance  -- ^ The instance to add
426
         -> T.OpResult Node    -- ^ The result of the operation,
427
                               -- either the new version of the node
428
                               -- or a failure mode
429
addPriEx force t inst =
430
  let iname = Instance.idx inst
431
      i_online = Instance.notOffline inst
432
      uses_disk = Instance.usesLocalStorage inst
433
      cur_dsk = fDsk t
434
      new_mem = decIf i_online (fMem t) (Instance.mem inst)
435
      new_dsk = decIf uses_disk cur_dsk (Instance.dsk inst)
436
      new_spindles = incIf uses_disk (instSpindles t) 1
437
      new_failn1 = new_mem <= rMem t
438
      new_ucpu = incIf i_online (uCpu t) (Instance.vcpus inst)
439
      new_pcpu = fromIntegral new_ucpu / tCpu t
440
      new_dp = computePDsk new_dsk (tDsk t)
441
      l_cpu = T.iPolicyVcpuRatio $ iPolicy t
442
      new_load = utilLoad t `T.addUtil` Instance.util inst
443
      inst_tags = Instance.tags inst
444
      old_tags = pTags t
445
      strict = not force
446
  in case () of
447
       _ | new_mem <= 0 -> T.OpFail T.FailMem
448
         | uses_disk && new_dsk <= 0 -> T.OpFail T.FailDisk
449
         | uses_disk && mDsk t > new_dp && strict -> T.OpFail T.FailDisk
450
         | uses_disk && new_spindles > hiSpindles t
451
             && strict -> T.OpFail T.FailDisk
452
         | new_failn1 && not (failN1 t) && strict -> T.OpFail T.FailMem
453
         | l_cpu >= 0 && l_cpu < new_pcpu && strict -> T.OpFail T.FailCPU
454
         | rejectAddTags old_tags inst_tags -> T.OpFail T.FailTags
455
         | otherwise ->
456
           let new_plist = iname:pList t
457
               new_mp = fromIntegral new_mem / tMem t
458
               r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
459
                     , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
460
                     , uCpu = new_ucpu, pCpu = new_pcpu
461
                     , utilLoad = new_load
462
                     , pTags = addTags old_tags inst_tags
463
                     , instSpindles = new_spindles
464
                     }
465
           in T.OpGood r
466

    
467
-- | Adds a secondary instance (basic version).
468
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
469
addSec = addSecEx False
470

    
471
-- | Adds a secondary instance (extended version).
472
addSecEx :: Bool -> Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
473
addSecEx force t inst pdx =
474
  let iname = Instance.idx inst
475
      old_peers = peers t
476
      old_mem = fMem t
477
      new_dsk = fDsk t - Instance.dsk inst
478
      new_spindles = instSpindles t + 1
479
      secondary_needed_mem = if Instance.usesSecMem inst
480
                               then Instance.mem inst
481
                               else 0
482
      new_peem = P.find pdx old_peers + secondary_needed_mem
483
      new_peers = P.add pdx new_peem old_peers
484
      new_rmem = max (rMem t) new_peem
485
      new_prem = fromIntegral new_rmem / tMem t
486
      new_failn1 = old_mem <= new_rmem
487
      new_dp = computePDsk new_dsk (tDsk t)
488
      old_load = utilLoad t
489
      new_load = old_load { T.dskWeight = T.dskWeight old_load +
490
                                          T.dskWeight (Instance.util inst) }
491
      strict = not force
492
  in case () of
493
       _ | not (Instance.hasSecondary inst) -> T.OpFail T.FailDisk
494
         | new_dsk <= 0 -> T.OpFail T.FailDisk
495
         | mDsk t > new_dp && strict -> T.OpFail T.FailDisk
496
         | new_spindles > hiSpindles t && strict -> T.OpFail T.FailDisk
497
         | secondary_needed_mem >= old_mem && strict -> T.OpFail T.FailMem
498
         | new_failn1 && not (failN1 t) && strict -> T.OpFail T.FailMem
499
         | otherwise ->
500
           let new_slist = iname:sList t
501
               r = t { sList = new_slist, fDsk = new_dsk
502
                     , peers = new_peers, failN1 = new_failn1
503
                     , rMem = new_rmem, pDsk = new_dp
504
                     , pRem = new_prem, utilLoad = new_load
505
                     , instSpindles = new_spindles
506
                     }
507
           in T.OpGood r
508

    
509
-- * Stats functions
510

    
511
-- | Computes the amount of available disk on a given node.
512
availDisk :: Node -> Int
513
availDisk t =
514
  let _f = fDsk t
515
      _l = loDsk t
516
  in if _f < _l
517
       then 0
518
       else _f - _l
519

    
520
-- | Computes the amount of used disk on a given node.
521
iDsk :: Node -> Int
522
iDsk t = truncate (tDsk t) - fDsk t
523

    
524
-- | Computes the amount of available memory on a given node.
525
availMem :: Node -> Int
526
availMem t =
527
  let _f = fMem t
528
      _l = rMem t
529
  in if _f < _l
530
       then 0
531
       else _f - _l
532

    
533
-- | Computes the amount of available memory on a given node.
534
availCpu :: Node -> Int
535
availCpu t =
536
  let _u = uCpu t
537
      _l = hiCpu t
538
  in if _l >= _u
539
       then _l - _u
540
       else 0
541

    
542
-- | The memory used by instances on a given node.
543
iMem :: Node -> Int
544
iMem t = truncate (tMem t) - nMem t - xMem t - fMem t
545

    
546
-- * Display functions
547

    
548
-- | Return a field for a given node.
549
showField :: Node   -- ^ Node which we're querying
550
          -> String -- ^ Field name
551
          -> String -- ^ Field value as string
552
showField t field =
553
  case field of
554
    "idx"  -> printf "%4d" $ idx t
555
    "name" -> alias t
556
    "fqdn" -> name t
557
    "status" -> case () of
558
                  _ | offline t -> "-"
559
                    | failN1 t -> "*"
560
                    | otherwise -> " "
561
    "tmem" -> printf "%5.0f" $ tMem t
562
    "nmem" -> printf "%5d" $ nMem t
563
    "xmem" -> printf "%5d" $ xMem t
564
    "fmem" -> printf "%5d" $ fMem t
565
    "imem" -> printf "%5d" $ iMem t
566
    "rmem" -> printf "%5d" $ rMem t
567
    "amem" -> printf "%5d" $ fMem t - rMem t
568
    "tdsk" -> printf "%5.0f" $ tDsk t / 1024
569
    "fdsk" -> printf "%5d" $ fDsk t `div` 1024
570
    "tcpu" -> printf "%4.0f" $ tCpu t
571
    "ucpu" -> printf "%4d" $ uCpu t
572
    "pcnt" -> printf "%3d" $ length (pList t)
573
    "scnt" -> printf "%3d" $ length (sList t)
574
    "plist" -> show $ pList t
575
    "slist" -> show $ sList t
576
    "pfmem" -> printf "%6.4f" $ pMem t
577
    "pfdsk" -> printf "%6.4f" $ pDsk t
578
    "rcpu"  -> printf "%5.2f" $ pCpu t
579
    "cload" -> printf "%5.3f" uC
580
    "mload" -> printf "%5.3f" uM
581
    "dload" -> printf "%5.3f" uD
582
    "nload" -> printf "%5.3f" uN
583
    "ptags" -> intercalate "," . map (uncurry (printf "%s=%d")) .
584
               Map.toList $ pTags t
585
    "peermap" -> show $ peers t
586
    "spindle_count" -> show $ spindleCount t
587
    "hi_spindles" -> show $ hiSpindles t
588
    "inst_spindles" -> show $ instSpindles t
589
    _ -> T.unknownField
590
  where
591
    T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
592
                T.dskWeight = uD, T.netWeight = uN } = utilLoad t
593

    
594
-- | Returns the header and numeric propery of a field.
595
showHeader :: String -> (String, Bool)
596
showHeader field =
597
  case field of
598
    "idx" -> ("Index", True)
599
    "name" -> ("Name", False)
600
    "fqdn" -> ("Name", False)
601
    "status" -> ("F", False)
602
    "tmem" -> ("t_mem", True)
603
    "nmem" -> ("n_mem", True)
604
    "xmem" -> ("x_mem", True)
605
    "fmem" -> ("f_mem", True)
606
    "imem" -> ("i_mem", True)
607
    "rmem" -> ("r_mem", True)
608
    "amem" -> ("a_mem", True)
609
    "tdsk" -> ("t_dsk", True)
610
    "fdsk" -> ("f_dsk", True)
611
    "tcpu" -> ("pcpu", True)
612
    "ucpu" -> ("vcpu", True)
613
    "pcnt" -> ("pcnt", True)
614
    "scnt" -> ("scnt", True)
615
    "plist" -> ("primaries", True)
616
    "slist" -> ("secondaries", True)
617
    "pfmem" -> ("p_fmem", True)
618
    "pfdsk" -> ("p_fdsk", True)
619
    "rcpu"  -> ("r_cpu", True)
620
    "cload" -> ("lCpu", True)
621
    "mload" -> ("lMem", True)
622
    "dload" -> ("lDsk", True)
623
    "nload" -> ("lNet", True)
624
    "ptags" -> ("PrimaryTags", False)
625
    "peermap" -> ("PeerMap", False)
626
    "spindle_count" -> ("NodeSpindles", True)
627
    "hi_spindles" -> ("MaxSpindles", True)
628
    "inst_spindles" -> ("InstSpindles", True)
629
    -- TODO: add node fields (group.uuid, group)
630
    _ -> (T.unknownField, False)
631

    
632
-- | String converter for the node list functionality.
633
list :: [String] -> Node -> [String]
634
list fields t = map (showField t) fields
635

    
636
-- | Constant holding the fields we're displaying by default.
637
defaultFields :: [String]
638
defaultFields =
639
  [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
640
  , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
641
  , "pfmem", "pfdsk", "rcpu"
642
  , "cload", "mload", "dload", "nload" ]
643

    
644
-- | Split a list of nodes into a list of (node group UUID, list of
645
-- associated nodes).
646
computeGroups :: [Node] -> [(T.Gdx, [Node])]
647
computeGroups nodes =
648
  let nodes' = sortBy (comparing group) nodes
649
      nodes'' = groupBy (\a b -> group a == group b) nodes'
650
  in map (\nl -> (group (head nl), nl)) nodes''