Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Node.hs @ 96f9b0a6

History | View | Annotate | Download (26.8 kB)

1
{-| Module describing a node.
2

    
3
    All updates are functional (copy-based) and return a new node with
4
    updated value.
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2009, 2010, 2011, 2012, 2013 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
  , setMaster
43
  , setNodeTags
44
  , setMdsk
45
  , setMcpu
46
  , setPolicy
47
  -- * Tag maps
48
  , addTags
49
  , delTags
50
  , rejectAddTags
51
  -- * Instance (re)location
52
  , removePri
53
  , removeSec
54
  , addPri
55
  , addPriEx
56
  , addSec
57
  , addSecEx
58
  -- * Stats
59
  , availDisk
60
  , availMem
61
  , availCpu
62
  , iMem
63
  , iDsk
64
  , conflictingPrimaries
65
  -- * Formatting
66
  , defaultFields
67
  , showHeader
68
  , showField
69
  , list
70
  -- * Misc stuff
71
  , AssocList
72
  , AllocElement
73
  , noSecondary
74
  , computeGroups
75
  , mkNodeGraph
76
  , mkRebootNodeGraph
77
  ) where
78

    
79
import Control.Monad (liftM, liftM2)
80
import Control.Applicative ((<$>), (<*>))
81
import qualified Data.Foldable as Foldable
82
import Data.Function (on)
83
import qualified Data.Graph as Graph
84
import qualified Data.IntMap as IntMap
85
import Data.List hiding (group)
86
import qualified Data.Map as Map
87
import Data.Ord (comparing)
88
import Text.Printf (printf)
89

    
90
import qualified Ganeti.HTools.Container as Container
91
import qualified Ganeti.HTools.Instance as Instance
92
import qualified Ganeti.HTools.PeerMap as P
93

    
94
import Ganeti.BasicTypes
95
import qualified Ganeti.HTools.Types as T
96

    
97
-- * Type declarations
98

    
99
-- | The tag map type.
100
type TagMap = Map.Map String Int
101

    
102
-- | The node type.
103
data Node = Node
104
  { name     :: String    -- ^ The node name
105
  , alias    :: String    -- ^ The shortened name (for display purposes)
106
  , tMem     :: Double    -- ^ Total memory (MiB)
107
  , nMem     :: Int       -- ^ Node memory (MiB)
108
  , fMem     :: Int       -- ^ Free memory (MiB)
109
  , xMem     :: Int       -- ^ Unaccounted memory (MiB)
110
  , tDsk     :: Double    -- ^ Total disk space (MiB)
111
  , fDsk     :: Int       -- ^ Free disk space (MiB)
112
  , tCpu     :: Double    -- ^ Total CPU count
113
  , uCpu     :: Int       -- ^ Used VCPU count
114
  , tSpindles :: Int      -- ^ Node spindles (spindle_count node parameter,
115
                          -- or actual spindles, see note below)
116
  , fSpindles :: Int      -- ^ Free spindles (see note below)
117
  , pList    :: [T.Idx]   -- ^ List of primary instance indices
118
  , sList    :: [T.Idx]   -- ^ List of secondary instance indices
119
  , idx      :: T.Ndx     -- ^ Internal index for book-keeping
120
  , peers    :: P.PeerMap -- ^ Pnode to instance mapping
121
  , failN1   :: Bool      -- ^ Whether the node has failed n1
122
  , rMem     :: Int       -- ^ Maximum memory needed for failover by
123
                          -- primaries of this node
124
  , pMem     :: Double    -- ^ Percent of free memory
125
  , pDsk     :: Double    -- ^ Percent of free disk
126
  , pRem     :: Double    -- ^ Percent of reserved memory
127
  , pCpu     :: Double    -- ^ Ratio of virtual to physical CPUs
128
  , mDsk     :: Double    -- ^ Minimum free disk ratio
129
  , loDsk    :: Int       -- ^ Autocomputed from mDsk low disk
130
                          -- threshold
131
  , hiCpu    :: Int       -- ^ Autocomputed from mCpu high cpu
132
                          -- threshold
133
  , hiSpindles :: Double  -- ^ Limit auto-computed from policy spindle_ratio
134
                          -- and the node spindle count (see note below)
135
  , instSpindles :: Double -- ^ Spindles used by instances (see note below)
136
  , offline  :: Bool      -- ^ Whether the node should not be used for
137
                          -- allocations and skipped from score
138
                          -- computations
139
  , isMaster :: Bool      -- ^ Whether the node is the master node
140
  , nTags    :: [String]  -- ^ The node tags for this node
141
  , utilPool :: T.DynUtil -- ^ Total utilisation capacity
142
  , utilLoad :: T.DynUtil -- ^ Sum of instance utilisation
143
  , pTags    :: TagMap    -- ^ Primary instance exclusion tags and their count
144
  , group    :: T.Gdx     -- ^ The node's group (index)
145
  , iPolicy  :: T.IPolicy -- ^ The instance policy (of the node's group)
146
  , exclStorage :: Bool   -- ^ Effective value of exclusive_storage
147
  } deriving (Show, Eq)
148
{- A note on how we handle spindles
149

    
150
With exclusive storage spindles is a resource, so we track the number of
151
spindles still available (fSpindles). This is the only reliable way, as some
152
spindles could be used outside of Ganeti. When exclusive storage is off,
153
spindles are a way to represent disk I/O pressure, and hence we track the amount
154
used by the instances. We compare it against 'hiSpindles', computed from the
155
instance policy, to avoid policy violations. In both cases we store the total
156
spindles in 'tSpindles'.
157
-}
158

    
159
instance T.Element Node where
160
  nameOf = name
161
  idxOf = idx
162
  setAlias = setAlias
163
  setIdx = setIdx
164
  allNames n = [name n, alias n]
165

    
166
-- | A simple name for the int, node association list.
167
type AssocList = [(T.Ndx, Node)]
168

    
169
-- | A simple name for a node map.
170
type List = Container.Container Node
171

    
172
-- | A simple name for an allocation element (here just for logistic
173
-- reasons).
174
type AllocElement = (List, Instance.Instance, [Node], T.Score)
175

    
176
-- | Constant node index for a non-moveable instance.
177
noSecondary :: T.Ndx
178
noSecondary = -1
179

    
180
-- * Helper functions
181

    
182
-- | Add a tag to a tagmap.
183
addTag :: TagMap -> String -> TagMap
184
addTag t s = Map.insertWith (+) s 1 t
185

    
186
-- | Add multiple tags.
187
addTags :: TagMap -> [String] -> TagMap
188
addTags = foldl' addTag
189

    
190
-- | Adjust or delete a tag from a tagmap.
191
delTag :: TagMap -> String -> TagMap
192
delTag t s = Map.update (\v -> if v > 1
193
                                 then Just (v-1)
194
                                 else Nothing)
195
             s t
196

    
197
-- | Remove multiple tags.
198
delTags :: TagMap -> [String] -> TagMap
199
delTags = foldl' delTag
200

    
201
-- | Check if we can add a list of tags to a tagmap.
202
rejectAddTags :: TagMap -> [String] -> Bool
203
rejectAddTags t = any (`Map.member` t)
204

    
205
-- | Check how many primary instances have conflicting tags. The
206
-- algorithm to compute this is to sum the count of all tags, then
207
-- subtract the size of the tag map (since each tag has at least one,
208
-- non-conflicting instance); this is equivalent to summing the
209
-- values in the tag map minus one.
210
conflictingPrimaries :: Node -> Int
211
conflictingPrimaries (Node { pTags = t }) = Foldable.sum t - Map.size t
212

    
213
-- | Helper function to increment a base value depending on the passed
214
-- boolean argument.
215
incIf :: (Num a) => Bool -> a -> a -> a
216
incIf True  base delta = base + delta
217
incIf False base _     = base
218

    
219
-- | Helper function to decrement a base value depending on the passed
220
-- boolean argument.
221
decIf :: (Num a) => Bool -> a -> a -> a
222
decIf True  base delta = base - delta
223
decIf False base _     = base
224

    
225
-- * Initialization functions
226

    
227
-- | Create a new node.
228
--
229
-- The index and the peers maps are empty, and will be need to be
230
-- update later via the 'setIdx' and 'buildPeers' functions.
231
create :: String -> Double -> Int -> Int -> Double
232
       -> Int -> Double -> Bool -> Int -> Int -> T.Gdx -> Bool -> Node
233
create name_init mem_t_init mem_n_init mem_f_init
234
       dsk_t_init dsk_f_init cpu_t_init offline_init spindles_t_init
235
       spindles_f_init group_init excl_stor =
236
  Node { name = name_init
237
       , alias = name_init
238
       , tMem = mem_t_init
239
       , nMem = mem_n_init
240
       , fMem = mem_f_init
241
       , tDsk = dsk_t_init
242
       , fDsk = dsk_f_init
243
       , tCpu = cpu_t_init
244
       , tSpindles = spindles_t_init
245
       , fSpindles = spindles_f_init
246
       , uCpu = 0
247
       , pList = []
248
       , sList = []
249
       , failN1 = True
250
       , idx = -1
251
       , peers = P.empty
252
       , rMem = 0
253
       , pMem = fromIntegral mem_f_init / mem_t_init
254
       , pDsk = computePDsk dsk_f_init dsk_t_init
255
       , pRem = 0
256
       , pCpu = 0
257
       , offline = offline_init
258
       , isMaster = False
259
       , nTags = []
260
       , xMem = 0
261
       , mDsk = T.defReservedDiskRatio
262
       , loDsk = mDskToloDsk T.defReservedDiskRatio dsk_t_init
263
       , hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio T.defIPolicy) cpu_t_init
264
       , hiSpindles = computeHiSpindles (T.iPolicySpindleRatio T.defIPolicy)
265
                      spindles_t_init
266
       , instSpindles = 0
267
       , utilPool = T.baseUtil
268
       , utilLoad = T.zeroUtil
269
       , pTags = Map.empty
270
       , group = group_init
271
       , iPolicy = T.defIPolicy
272
       , exclStorage = excl_stor
273
       }
274

    
275
-- | Conversion formula from mDsk\/tDsk to loDsk.
276
mDskToloDsk :: Double -> Double -> Int
277
mDskToloDsk mval = floor . (mval *)
278

    
279
-- | Conversion formula from mCpu\/tCpu to hiCpu.
280
mCpuTohiCpu :: Double -> Double -> Int
281
mCpuTohiCpu mval = floor . (mval *)
282

    
283
-- | Conversiojn formula from spindles and spindle ratio to hiSpindles.
284
computeHiSpindles :: Double -> Int -> Double
285
computeHiSpindles spindle_ratio = (spindle_ratio *) . fromIntegral
286

    
287
-- | Changes the index.
288
--
289
-- This is used only during the building of the data structures.
290
setIdx :: Node -> T.Ndx -> Node
291
setIdx t i = t {idx = i}
292

    
293
-- | Changes the alias.
294
--
295
-- This is used only during the building of the data structures.
296
setAlias :: Node -> String -> Node
297
setAlias t s = t { alias = s }
298

    
299
-- | Sets the offline attribute.
300
setOffline :: Node -> Bool -> Node
301
setOffline t val = t { offline = val }
302

    
303
-- | Sets the master attribute
304
setMaster :: Node -> Bool -> Node
305
setMaster t val = t { isMaster = val }
306

    
307
-- | Sets the node tags attribute
308
setNodeTags :: Node -> [String] -> Node
309
setNodeTags t val = t { nTags = val }
310

    
311
-- | Sets the unnaccounted memory.
312
setXmem :: Node -> Int -> Node
313
setXmem t val = t { xMem = val }
314

    
315
-- | Sets the max disk usage ratio.
316
setMdsk :: Node -> Double -> Node
317
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
318

    
319
-- | Sets the max cpu usage ratio. This will update the node's
320
-- ipolicy, losing sharing (but it should be a seldomly done operation).
321
setMcpu :: Node -> Double -> Node
322
setMcpu t val =
323
  let new_ipol = (iPolicy t) { T.iPolicyVcpuRatio = val }
324
  in t { hiCpu = mCpuTohiCpu val (tCpu t), iPolicy = new_ipol }
325

    
326
-- | Sets the policy.
327
setPolicy :: T.IPolicy -> Node -> Node
328
setPolicy pol node =
329
  node { iPolicy = pol
330
       , hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio pol) (tCpu node)
331
       , hiSpindles = computeHiSpindles (T.iPolicySpindleRatio pol)
332
                      (tSpindles node)
333
       }
334

    
335
-- | Computes the maximum reserved memory for peers from a peer map.
336
computeMaxRes :: P.PeerMap -> P.Elem
337
computeMaxRes = P.maxElem
338

    
339
-- | Builds the peer map for a given node.
340
buildPeers :: Node -> Instance.List -> Node
341
buildPeers t il =
342
  let mdata = map
343
              (\i_idx -> let inst = Container.find i_idx il
344
                             mem = if Instance.usesSecMem inst
345
                                     then Instance.mem inst
346
                                     else 0
347
                         in (Instance.pNode inst, mem))
348
              (sList t)
349
      pmap = P.accumArray (+) mdata
350
      new_rmem = computeMaxRes pmap
351
      new_failN1 = fMem t <= new_rmem
352
      new_prem = fromIntegral new_rmem / tMem t
353
  in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
354

    
355
-- | Calculate the new spindle usage
356
calcSpindleUse :: Node -> Instance.Instance -> Double
357
calcSpindleUse n i = incIf (Instance.usesLocalStorage i) (instSpindles n)
358
                       (fromIntegral $ Instance.spindleUse i)
359

    
360
-- | Assigns an instance to a node as primary and update the used VCPU
361
-- count, utilisation data and tags map.
362
setPri :: Node -> Instance.Instance -> Node
363
setPri t inst = t { pList = Instance.idx inst:pList t
364
                  , uCpu = new_count
365
                  , pCpu = fromIntegral new_count / tCpu t
366
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
367
                  , pTags = addTags (pTags t) (Instance.exclTags inst)
368
                  , instSpindles = calcSpindleUse t inst
369
                  }
370
  where new_count = Instance.applyIfOnline inst (+ Instance.vcpus inst)
371
                    (uCpu t )
372

    
373
-- | Assigns an instance to a node as secondary without other updates.
374
setSec :: Node -> Instance.Instance -> Node
375
setSec t inst = t { sList = Instance.idx inst:sList t
376
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
377
                                          T.dskWeight (Instance.util inst) }
378
                  , instSpindles = calcSpindleUse t inst
379
                  }
380
  where old_load = utilLoad t
381

    
382
-- | Computes the new 'pDsk' value, handling nodes without local disk
383
-- storage (we consider all their disk used).
384
computePDsk :: Int -> Double -> Double
385
computePDsk _    0     = 1
386
computePDsk used total = fromIntegral used / total
387

    
388
-- * Update functions
389

    
390
-- | Sets the free memory.
391
setFmem :: Node -> Int -> Node
392
setFmem t new_mem =
393
  let new_n1 = new_mem < rMem t
394
      new_mp = fromIntegral new_mem / tMem t
395
  in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
396

    
397
-- | Removes a primary instance.
398
removePri :: Node -> Instance.Instance -> Node
399
removePri t inst =
400
  let iname = Instance.idx inst
401
      i_online = Instance.notOffline inst
402
      uses_disk = Instance.usesLocalStorage inst
403
      new_plist = delete iname (pList t)
404
      new_mem = incIf i_online (fMem t) (Instance.mem inst)
405
      new_dsk = incIf uses_disk (fDsk t) (Instance.dsk inst)
406
      new_spindles = decIf uses_disk (instSpindles t) 1
407
      new_mp = fromIntegral new_mem / tMem t
408
      new_dp = computePDsk new_dsk (tDsk t)
409
      new_failn1 = new_mem <= rMem t
410
      new_ucpu = decIf i_online (uCpu t) (Instance.vcpus inst)
411
      new_rcpu = fromIntegral new_ucpu / tCpu t
412
      new_load = utilLoad t `T.subUtil` Instance.util inst
413
  in t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
414
       , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
415
       , uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load
416
       , pTags = delTags (pTags t) (Instance.exclTags inst)
417
       , instSpindles = new_spindles
418
       }
419

    
420
-- | Removes a secondary instance.
421
removeSec :: Node -> Instance.Instance -> Node
422
removeSec t inst =
423
  let iname = Instance.idx inst
424
      uses_disk = Instance.usesLocalStorage inst
425
      cur_dsk = fDsk t
426
      pnode = Instance.pNode inst
427
      new_slist = delete iname (sList t)
428
      new_dsk = incIf uses_disk cur_dsk (Instance.dsk inst)
429
      new_spindles = decIf uses_disk (instSpindles t) 1
430
      old_peers = peers t
431
      old_peem = P.find pnode old_peers
432
      new_peem = decIf (Instance.usesSecMem inst) old_peem (Instance.mem inst)
433
      new_peers = if new_peem > 0
434
                    then P.add pnode new_peem old_peers
435
                    else P.remove pnode old_peers
436
      old_rmem = rMem t
437
      new_rmem = if old_peem < old_rmem
438
                   then old_rmem
439
                   else computeMaxRes new_peers
440
      new_prem = fromIntegral new_rmem / tMem t
441
      new_failn1 = fMem t <= new_rmem
442
      new_dp = computePDsk new_dsk (tDsk t)
443
      old_load = utilLoad t
444
      new_load = old_load { T.dskWeight = T.dskWeight old_load -
445
                                          T.dskWeight (Instance.util inst) }
446
  in t { sList = new_slist, fDsk = new_dsk, peers = new_peers
447
       , failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
448
       , pRem = new_prem, utilLoad = new_load
449
       , instSpindles = new_spindles
450
       }
451

    
452
-- | Adds a primary instance (basic version).
453
addPri :: Node -> Instance.Instance -> T.OpResult Node
454
addPri = addPriEx False
455

    
456
-- | Adds a primary instance (extended version).
457
addPriEx :: Bool               -- ^ Whether to override the N+1 and
458
                               -- other /soft/ checks, useful if we
459
                               -- come from a worse status
460
                               -- (e.g. offline)
461
         -> Node               -- ^ The target node
462
         -> Instance.Instance  -- ^ The instance to add
463
         -> T.OpResult Node    -- ^ The result of the operation,
464
                               -- either the new version of the node
465
                               -- or a failure mode
466
addPriEx force t inst =
467
  let iname = Instance.idx inst
468
      i_online = Instance.notOffline inst
469
      uses_disk = Instance.usesLocalStorage inst
470
      cur_dsk = fDsk t
471
      new_mem = decIf i_online (fMem t) (Instance.mem inst)
472
      new_dsk = decIf uses_disk cur_dsk (Instance.dsk inst)
473
      new_spindles = incIf uses_disk (instSpindles t) 1
474
      new_failn1 = new_mem <= rMem t
475
      new_ucpu = incIf i_online (uCpu t) (Instance.vcpus inst)
476
      new_pcpu = fromIntegral new_ucpu / tCpu t
477
      new_dp = computePDsk new_dsk (tDsk t)
478
      l_cpu = T.iPolicyVcpuRatio $ iPolicy t
479
      new_load = utilLoad t `T.addUtil` Instance.util inst
480
      inst_tags = Instance.exclTags inst
481
      old_tags = pTags t
482
      strict = not force
483
  in case () of
484
       _ | new_mem <= 0 -> Bad T.FailMem
485
         | uses_disk && new_dsk <= 0 -> Bad T.FailDisk
486
         | uses_disk && mDsk t > new_dp && strict -> Bad T.FailDisk
487
         | uses_disk && new_spindles > hiSpindles t
488
             && strict -> Bad T.FailDisk
489
         | new_failn1 && not (failN1 t) && strict -> Bad T.FailMem
490
         | l_cpu >= 0 && l_cpu < new_pcpu && strict -> Bad T.FailCPU
491
         | rejectAddTags old_tags inst_tags -> Bad T.FailTags
492
         | otherwise ->
493
           let new_plist = iname:pList t
494
               new_mp = fromIntegral new_mem / tMem t
495
               r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
496
                     , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
497
                     , uCpu = new_ucpu, pCpu = new_pcpu
498
                     , utilLoad = new_load
499
                     , pTags = addTags old_tags inst_tags
500
                     , instSpindles = new_spindles
501
                     }
502
           in Ok r
503

    
504
-- | Adds a secondary instance (basic version).
505
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
506
addSec = addSecEx False
507

    
508
-- | Adds a secondary instance (extended version).
509
addSecEx :: Bool -> Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
510
addSecEx force t inst pdx =
511
  let iname = Instance.idx inst
512
      old_peers = peers t
513
      old_mem = fMem t
514
      new_dsk = fDsk t - Instance.dsk inst
515
      new_spindles = instSpindles t + 1
516
      secondary_needed_mem = if Instance.usesSecMem inst
517
                               then Instance.mem inst
518
                               else 0
519
      new_peem = P.find pdx old_peers + secondary_needed_mem
520
      new_peers = P.add pdx new_peem old_peers
521
      new_rmem = max (rMem t) new_peem
522
      new_prem = fromIntegral new_rmem / tMem t
523
      new_failn1 = old_mem <= new_rmem
524
      new_dp = computePDsk new_dsk (tDsk t)
525
      old_load = utilLoad t
526
      new_load = old_load { T.dskWeight = T.dskWeight old_load +
527
                                          T.dskWeight (Instance.util inst) }
528
      strict = not force
529
  in case () of
530
       _ | not (Instance.hasSecondary inst) -> Bad T.FailDisk
531
         | new_dsk <= 0 -> Bad T.FailDisk
532
         | mDsk t > new_dp && strict -> Bad T.FailDisk
533
         | new_spindles > hiSpindles t && strict -> Bad T.FailDisk
534
         | secondary_needed_mem >= old_mem && strict -> Bad T.FailMem
535
         | new_failn1 && not (failN1 t) && strict -> Bad T.FailMem
536
         | otherwise ->
537
           let new_slist = iname:sList t
538
               r = t { sList = new_slist, fDsk = new_dsk
539
                     , peers = new_peers, failN1 = new_failn1
540
                     , rMem = new_rmem, pDsk = new_dp
541
                     , pRem = new_prem, utilLoad = new_load
542
                     , instSpindles = new_spindles
543
                     }
544
           in Ok r
545

    
546
-- * Stats functions
547

    
548
-- | Computes the amount of available disk on a given node.
549
availDisk :: Node -> Int
550
availDisk t =
551
  let _f = fDsk t
552
      _l = loDsk t
553
  in if _f < _l
554
       then 0
555
       else _f - _l
556

    
557
-- | Computes the amount of used disk on a given node.
558
iDsk :: Node -> Int
559
iDsk t = truncate (tDsk t) - fDsk t
560

    
561
-- | Computes the amount of available memory on a given node.
562
availMem :: Node -> Int
563
availMem t =
564
  let _f = fMem t
565
      _l = rMem t
566
  in if _f < _l
567
       then 0
568
       else _f - _l
569

    
570
-- | Computes the amount of available memory on a given node.
571
availCpu :: Node -> Int
572
availCpu t =
573
  let _u = uCpu t
574
      _l = hiCpu t
575
  in if _l >= _u
576
       then _l - _u
577
       else 0
578

    
579
-- | The memory used by instances on a given node.
580
iMem :: Node -> Int
581
iMem t = truncate (tMem t) - nMem t - xMem t - fMem t
582

    
583
-- * Node graph functions
584
-- These functions do the transformations needed so that nodes can be
585
-- represented as a graph connected by the instances that are replicated
586
-- on them.
587

    
588
-- * Making of a Graph from a node/instance list
589

    
590
-- | Transform an instance into a list of edges on the node graph
591
instanceToEdges :: Instance.Instance -> [Graph.Edge]
592
instanceToEdges i
593
  | Instance.hasSecondary i = [(pnode,snode), (snode,pnode)]
594
  | otherwise = []
595
    where pnode = Instance.pNode i
596
          snode = Instance.sNode i
597

    
598
-- | Transform the list of instances into list of destination edges
599
instancesToEdges :: Instance.List -> [Graph.Edge]
600
instancesToEdges = concatMap instanceToEdges . Container.elems
601

    
602
-- | Transform the list of nodes into vertices bounds.
603
-- Returns Nothing is the list is empty.
604
nodesToBounds :: List -> Maybe Graph.Bounds
605
nodesToBounds nl = liftM2 (,) nmin nmax
606
    where nmin = fmap (fst . fst) (IntMap.minViewWithKey nl)
607
          nmax = fmap (fst . fst) (IntMap.maxViewWithKey nl)
608

    
609
-- | The clique of the primary nodes of the instances with a given secondary.
610
-- Return the full graph of those nodes that are primary node of at least one
611
-- instance that has the given node as secondary.
612
nodeToSharedSecondaryEdge :: Instance.List -> Node -> [Graph.Edge]
613
nodeToSharedSecondaryEdge il n = (,) <$> primaries <*> primaries
614
  where primaries = map (Instance.pNode . flip Container.find il) $ sList n
615

    
616

    
617
-- | Predicate of an edge having both vertices in a set of nodes.
618
filterValid :: List -> [Graph.Edge] -> [Graph.Edge]
619
filterValid nl  =  filter $ \(x,y) -> IntMap.member x nl && IntMap.member y nl
620

    
621
-- | Transform a Node + Instance list into a NodeGraph type.
622
-- Returns Nothing if the node list is empty.
623
mkNodeGraph :: List -> Instance.List -> Maybe Graph.Graph
624
mkNodeGraph nl il =
625
  liftM (`Graph.buildG` (filterValid nl . instancesToEdges $ il))
626
  (nodesToBounds nl)
627

    
628
-- | Transform a Nodes + Instances into a NodeGraph with all reboot exclusions.
629
-- This includes edges between nodes that are the primary nodes of instances
630
-- that have the same secondary node. Nodes not in the node list will not be
631
-- part of the graph, but they are still considered for the edges arising from
632
-- two instances having the same secondary node.
633
-- Return Nothing if the node list is empty.
634
mkRebootNodeGraph :: List -> List -> Instance.List -> Maybe Graph.Graph
635
mkRebootNodeGraph allnodes nl il =
636
  liftM (`Graph.buildG` filterValid nl edges) (nodesToBounds nl)
637
  where
638
    edges = instancesToEdges il `union`
639
            (Container.elems allnodes >>= nodeToSharedSecondaryEdge il) 
640

    
641
-- * Display functions
642

    
643
-- | Return a field for a given node.
644
showField :: Node   -- ^ Node which we're querying
645
          -> String -- ^ Field name
646
          -> String -- ^ Field value as string
647
showField t field =
648
  case field of
649
    "idx"  -> printf "%4d" $ idx t
650
    "name" -> alias t
651
    "fqdn" -> name t
652
    "status" -> case () of
653
                  _ | offline t -> "-"
654
                    | failN1 t -> "*"
655
                    | otherwise -> " "
656
    "tmem" -> printf "%5.0f" $ tMem t
657
    "nmem" -> printf "%5d" $ nMem t
658
    "xmem" -> printf "%5d" $ xMem t
659
    "fmem" -> printf "%5d" $ fMem t
660
    "imem" -> printf "%5d" $ iMem t
661
    "rmem" -> printf "%5d" $ rMem t
662
    "amem" -> printf "%5d" $ fMem t - rMem t
663
    "tdsk" -> printf "%5.0f" $ tDsk t / 1024
664
    "fdsk" -> printf "%5d" $ fDsk t `div` 1024
665
    "tcpu" -> printf "%4.0f" $ tCpu t
666
    "ucpu" -> printf "%4d" $ uCpu t
667
    "pcnt" -> printf "%3d" $ length (pList t)
668
    "scnt" -> printf "%3d" $ length (sList t)
669
    "plist" -> show $ pList t
670
    "slist" -> show $ sList t
671
    "pfmem" -> printf "%6.4f" $ pMem t
672
    "pfdsk" -> printf "%6.4f" $ pDsk t
673
    "rcpu"  -> printf "%5.2f" $ pCpu t
674
    "cload" -> printf "%5.3f" uC
675
    "mload" -> printf "%5.3f" uM
676
    "dload" -> printf "%5.3f" uD
677
    "nload" -> printf "%5.3f" uN
678
    "ptags" -> intercalate "," . map (uncurry (printf "%s=%d")) .
679
               Map.toList $ pTags t
680
    "peermap" -> show $ peers t
681
    "spindle_count" -> show $ tSpindles t
682
    "hi_spindles" -> show $ hiSpindles t
683
    "inst_spindles" -> show $ instSpindles t
684
    _ -> T.unknownField
685
  where
686
    T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
687
                T.dskWeight = uD, T.netWeight = uN } = utilLoad t
688

    
689
-- | Returns the header and numeric propery of a field.
690
showHeader :: String -> (String, Bool)
691
showHeader field =
692
  case field of
693
    "idx" -> ("Index", True)
694
    "name" -> ("Name", False)
695
    "fqdn" -> ("Name", False)
696
    "status" -> ("F", False)
697
    "tmem" -> ("t_mem", True)
698
    "nmem" -> ("n_mem", True)
699
    "xmem" -> ("x_mem", True)
700
    "fmem" -> ("f_mem", True)
701
    "imem" -> ("i_mem", True)
702
    "rmem" -> ("r_mem", True)
703
    "amem" -> ("a_mem", True)
704
    "tdsk" -> ("t_dsk", True)
705
    "fdsk" -> ("f_dsk", True)
706
    "tcpu" -> ("pcpu", True)
707
    "ucpu" -> ("vcpu", True)
708
    "pcnt" -> ("pcnt", True)
709
    "scnt" -> ("scnt", True)
710
    "plist" -> ("primaries", True)
711
    "slist" -> ("secondaries", True)
712
    "pfmem" -> ("p_fmem", True)
713
    "pfdsk" -> ("p_fdsk", True)
714
    "rcpu"  -> ("r_cpu", True)
715
    "cload" -> ("lCpu", True)
716
    "mload" -> ("lMem", True)
717
    "dload" -> ("lDsk", True)
718
    "nload" -> ("lNet", True)
719
    "ptags" -> ("PrimaryTags", False)
720
    "peermap" -> ("PeerMap", False)
721
    "spindle_count" -> ("NodeSpindles", True)
722
    "hi_spindles" -> ("MaxSpindles", True)
723
    "inst_spindles" -> ("InstSpindles", True)
724
    -- TODO: add node fields (group.uuid, group)
725
    _ -> (T.unknownField, False)
726

    
727
-- | String converter for the node list functionality.
728
list :: [String] -> Node -> [String]
729
list fields t = map (showField t) fields
730

    
731
-- | Constant holding the fields we're displaying by default.
732
defaultFields :: [String]
733
defaultFields =
734
  [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
735
  , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
736
  , "pfmem", "pfdsk", "rcpu"
737
  , "cload", "mload", "dload", "nload" ]
738

    
739
{-# ANN computeGroups "HLint: ignore Use alternative" #-}
740
-- | Split a list of nodes into a list of (node group UUID, list of
741
-- associated nodes).
742
computeGroups :: [Node] -> [(T.Gdx, [Node])]
743
computeGroups nodes =
744
  let nodes' = sortBy (comparing group) nodes
745
      nodes'' = groupBy ((==) `on` group) nodes'
746
  -- use of head here is OK, since groupBy returns non-empty lists; if
747
  -- you remove groupBy, also remove use of head
748
  in map (\nl -> (group (head nl), nl)) nodes''