Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Node.hs @ 825f8cee

History | View | Annotate | Download (28.6 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 = if excl_stor
255
                then computePDsk spindles_f_init $ fromIntegral spindles_t_init
256
                else computePDsk dsk_f_init dsk_t_init
257
       , pRem = 0
258
       , pCpu = 0
259
       , offline = offline_init
260
       , isMaster = False
261
       , nTags = []
262
       , xMem = 0
263
       , mDsk = T.defReservedDiskRatio
264
       , loDsk = mDskToloDsk T.defReservedDiskRatio dsk_t_init
265
       , hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio T.defIPolicy) cpu_t_init
266
       , hiSpindles = computeHiSpindles (T.iPolicySpindleRatio T.defIPolicy)
267
                      spindles_t_init
268
       , instSpindles = 0
269
       , utilPool = T.baseUtil
270
       , utilLoad = T.zeroUtil
271
       , pTags = Map.empty
272
       , group = group_init
273
       , iPolicy = T.defIPolicy
274
       , exclStorage = excl_stor
275
       }
276

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
357
-- | Calculate the new spindle usage
358
calcSpindleUse ::
359
                  Bool -- Action: True = adding instance, False = removing it
360
               -> Node -> Instance.Instance -> Double
361
calcSpindleUse _ (Node {exclStorage = True}) _ = 0.0
362
calcSpindleUse act n@(Node {exclStorage = False}) i =
363
  f (Instance.usesLocalStorage i) (instSpindles n)
364
    (fromIntegral $ Instance.spindleUse i)
365
    where
366
      f :: Bool -> Double -> Double -> Double -- avoid monomorphism restriction
367
      f = if act then incIf else decIf
368

    
369
-- | Calculate the new number of free spindles
370
calcNewFreeSpindles ::
371
                       Bool -- Action: True = adding instance, False = removing
372
                    -> Node -> Instance.Instance -> Int
373
calcNewFreeSpindles _ (Node {exclStorage = False}) _ = 0
374
calcNewFreeSpindles act n@(Node {exclStorage = True}) i =
375
  case Instance.getTotalSpindles i of
376
    Nothing -> if act
377
               then -1 -- Force a spindle error, so the instance don't go here
378
               else fSpindles n -- No change, as we aren't sure
379
    Just s -> (if act then (-) else (+)) (fSpindles n) s
380

    
381
-- | Assigns an instance to a node as primary and update the used VCPU
382
-- count, utilisation data and tags map.
383
setPri :: Node -> Instance.Instance -> Node
384
setPri t inst = t { pList = Instance.idx inst:pList t
385
                  , uCpu = new_count
386
                  , pCpu = fromIntegral new_count / tCpu t
387
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
388
                  , pTags = addTags (pTags t) (Instance.exclTags inst)
389
                  , instSpindles = calcSpindleUse True t inst
390
                  }
391
  where new_count = Instance.applyIfOnline inst (+ Instance.vcpus inst)
392
                    (uCpu t )
393

    
394
-- | Assigns an instance to a node as secondary and updates disk utilisation.
395
setSec :: Node -> Instance.Instance -> Node
396
setSec t inst = t { sList = Instance.idx inst:sList t
397
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
398
                                          T.dskWeight (Instance.util inst) }
399
                  , instSpindles = calcSpindleUse True t inst
400
                  }
401
  where old_load = utilLoad t
402

    
403
-- | Computes the new 'pDsk' value, handling nodes without local disk
404
-- storage (we consider all their disk unused).
405
computePDsk :: Int -> Double -> Double
406
computePDsk _    0     = 1
407
computePDsk free total = fromIntegral free / total
408

    
409
-- | Computes the new 'pDsk' value, handling the exclusive storage state.
410
computeNewPDsk :: Node -> Int -> Int -> Double
411
computeNewPDsk node new_free_sp new_free_dsk =
412
  if exclStorage node
413
  then computePDsk new_free_sp . fromIntegral $ tSpindles node
414
  else computePDsk new_free_dsk $ tDsk node
415

    
416
-- * Update functions
417

    
418
-- | Sets the free memory.
419
setFmem :: Node -> Int -> Node
420
setFmem t new_mem =
421
  let new_n1 = new_mem < rMem t
422
      new_mp = fromIntegral new_mem / tMem t
423
  in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
424

    
425
-- | Removes a primary instance.
426
removePri :: Node -> Instance.Instance -> Node
427
removePri t inst =
428
  let iname = Instance.idx inst
429
      i_online = Instance.notOffline inst
430
      uses_disk = Instance.usesLocalStorage inst
431
      new_plist = delete iname (pList t)
432
      new_mem = incIf i_online (fMem t) (Instance.mem inst)
433
      new_dsk = incIf uses_disk (fDsk t) (Instance.dsk inst)
434
      new_free_sp = calcNewFreeSpindles False t inst
435
      new_inst_sp = calcSpindleUse False t inst
436
      new_mp = fromIntegral new_mem / tMem t
437
      new_dp = computeNewPDsk t new_free_sp new_dsk
438
      new_failn1 = new_mem <= rMem t
439
      new_ucpu = decIf i_online (uCpu t) (Instance.vcpus inst)
440
      new_rcpu = fromIntegral new_ucpu / tCpu t
441
      new_load = utilLoad t `T.subUtil` Instance.util inst
442
  in t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
443
       , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
444
       , uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load
445
       , pTags = delTags (pTags t) (Instance.exclTags inst)
446
       , instSpindles = new_inst_sp, fSpindles = new_free_sp
447
       }
448

    
449
-- | Removes a secondary instance.
450
removeSec :: Node -> Instance.Instance -> Node
451
removeSec t inst =
452
  let iname = Instance.idx inst
453
      uses_disk = Instance.usesLocalStorage inst
454
      cur_dsk = fDsk t
455
      pnode = Instance.pNode inst
456
      new_slist = delete iname (sList t)
457
      new_dsk = incIf uses_disk cur_dsk (Instance.dsk inst)
458
      new_free_sp = calcNewFreeSpindles False t inst
459
      new_inst_sp = calcSpindleUse False t inst
460
      old_peers = peers t
461
      old_peem = P.find pnode old_peers
462
      new_peem = decIf (Instance.usesSecMem inst) old_peem (Instance.mem inst)
463
      new_peers = if new_peem > 0
464
                    then P.add pnode new_peem old_peers
465
                    else P.remove pnode old_peers
466
      old_rmem = rMem t
467
      new_rmem = if old_peem < old_rmem
468
                   then old_rmem
469
                   else computeMaxRes new_peers
470
      new_prem = fromIntegral new_rmem / tMem t
471
      new_failn1 = fMem t <= new_rmem
472
      new_dp = computeNewPDsk t new_free_sp new_dsk
473
      old_load = utilLoad t
474
      new_load = old_load { T.dskWeight = T.dskWeight old_load -
475
                                          T.dskWeight (Instance.util inst) }
476
  in t { sList = new_slist, fDsk = new_dsk, peers = new_peers
477
       , failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
478
       , pRem = new_prem, utilLoad = new_load
479
       , instSpindles = new_inst_sp, fSpindles = new_free_sp
480
       }
481

    
482
-- | Adds a primary instance (basic version).
483
addPri :: Node -> Instance.Instance -> T.OpResult Node
484
addPri = addPriEx False
485

    
486
-- | Adds a primary instance (extended version).
487
addPriEx :: Bool               -- ^ Whether to override the N+1 and
488
                               -- other /soft/ checks, useful if we
489
                               -- come from a worse status
490
                               -- (e.g. offline)
491
         -> Node               -- ^ The target node
492
         -> Instance.Instance  -- ^ The instance to add
493
         -> T.OpResult Node    -- ^ The result of the operation,
494
                               -- either the new version of the node
495
                               -- or a failure mode
496
addPriEx force t inst =
497
  let iname = Instance.idx inst
498
      i_online = Instance.notOffline inst
499
      uses_disk = Instance.usesLocalStorage inst
500
      cur_dsk = fDsk t
501
      new_mem = decIf i_online (fMem t) (Instance.mem inst)
502
      new_dsk = decIf uses_disk cur_dsk (Instance.dsk inst)
503
      new_free_sp = calcNewFreeSpindles True t inst
504
      new_inst_sp = calcSpindleUse True t inst
505
      new_failn1 = new_mem <= rMem t
506
      new_ucpu = incIf i_online (uCpu t) (Instance.vcpus inst)
507
      new_pcpu = fromIntegral new_ucpu / tCpu t
508
      new_dp = computeNewPDsk t new_free_sp new_dsk
509
      l_cpu = T.iPolicyVcpuRatio $ iPolicy t
510
      new_load = utilLoad t `T.addUtil` Instance.util inst
511
      inst_tags = Instance.exclTags inst
512
      old_tags = pTags t
513
      strict = not force
514
  in case () of
515
       _ | new_mem <= 0 -> Bad T.FailMem
516
         | uses_disk && new_dsk <= 0 -> Bad T.FailDisk
517
         | uses_disk && new_dsk < loDsk t && strict -> Bad T.FailDisk
518
         | uses_disk && exclStorage t && new_free_sp < 0 -> Bad T.FailSpindles
519
         | uses_disk && new_inst_sp > hiSpindles t && strict -> Bad T.FailDisk
520
         | new_failn1 && not (failN1 t) && strict -> Bad T.FailMem
521
         | l_cpu >= 0 && l_cpu < new_pcpu && strict -> Bad T.FailCPU
522
         | rejectAddTags old_tags inst_tags -> Bad T.FailTags
523
         | otherwise ->
524
           let new_plist = iname:pList t
525
               new_mp = fromIntegral new_mem / tMem t
526
               r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
527
                     , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
528
                     , uCpu = new_ucpu, pCpu = new_pcpu
529
                     , utilLoad = new_load
530
                     , pTags = addTags old_tags inst_tags
531
                     , instSpindles = new_inst_sp
532
                     , fSpindles = new_free_sp
533
                     }
534
           in Ok r
535

    
536
-- | Adds a secondary instance (basic version).
537
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
538
addSec = addSecEx False
539

    
540
-- | Adds a secondary instance (extended version).
541
addSecEx :: Bool -> Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
542
addSecEx force t inst pdx =
543
  let iname = Instance.idx inst
544
      old_peers = peers t
545
      old_mem = fMem t
546
      new_dsk = fDsk t - Instance.dsk inst
547
      new_free_sp = calcNewFreeSpindles True t inst
548
      new_inst_sp = calcSpindleUse True t inst
549
      secondary_needed_mem = if Instance.usesSecMem inst
550
                               then Instance.mem inst
551
                               else 0
552
      new_peem = P.find pdx old_peers + secondary_needed_mem
553
      new_peers = P.add pdx new_peem old_peers
554
      new_rmem = max (rMem t) new_peem
555
      new_prem = fromIntegral new_rmem / tMem t
556
      new_failn1 = old_mem <= new_rmem
557
      new_dp = computeNewPDsk t new_free_sp new_dsk
558
      old_load = utilLoad t
559
      new_load = old_load { T.dskWeight = T.dskWeight old_load +
560
                                          T.dskWeight (Instance.util inst) }
561
      strict = not force
562
  in case () of
563
       _ | not (Instance.hasSecondary inst) -> Bad T.FailDisk
564
         | new_dsk <= 0 -> Bad T.FailDisk
565
         | new_dsk < loDsk t && strict -> Bad T.FailDisk
566
         | exclStorage t && new_free_sp < 0 -> Bad T.FailSpindles
567
         | new_inst_sp > hiSpindles t && strict -> Bad T.FailDisk
568
         | secondary_needed_mem >= old_mem && strict -> Bad T.FailMem
569
         | new_failn1 && not (failN1 t) && strict -> Bad T.FailMem
570
         | otherwise ->
571
           let new_slist = iname:sList t
572
               r = t { sList = new_slist, fDsk = new_dsk
573
                     , peers = new_peers, failN1 = new_failn1
574
                     , rMem = new_rmem, pDsk = new_dp
575
                     , pRem = new_prem, utilLoad = new_load
576
                     , instSpindles = new_inst_sp
577
                     , fSpindles = new_free_sp
578
                     }
579
           in Ok r
580

    
581
-- * Stats functions
582

    
583
-- | Computes the amount of available disk on a given node.
584
availDisk :: Node -> Int
585
availDisk t =
586
  let _f = fDsk t
587
      _l = loDsk t
588
  in if _f < _l
589
       then 0
590
       else _f - _l
591

    
592
-- | Computes the amount of used disk on a given node.
593
iDsk :: Node -> Int
594
iDsk t = truncate (tDsk t) - fDsk t
595

    
596
-- | Computes the amount of available memory on a given node.
597
availMem :: Node -> Int
598
availMem t =
599
  let _f = fMem t
600
      _l = rMem t
601
  in if _f < _l
602
       then 0
603
       else _f - _l
604

    
605
-- | Computes the amount of available memory on a given node.
606
availCpu :: Node -> Int
607
availCpu t =
608
  let _u = uCpu t
609
      _l = hiCpu t
610
  in if _l >= _u
611
       then _l - _u
612
       else 0
613

    
614
-- | The memory used by instances on a given node.
615
iMem :: Node -> Int
616
iMem t = truncate (tMem t) - nMem t - xMem t - fMem t
617

    
618
-- * Node graph functions
619
-- These functions do the transformations needed so that nodes can be
620
-- represented as a graph connected by the instances that are replicated
621
-- on them.
622

    
623
-- * Making of a Graph from a node/instance list
624

    
625
-- | Transform an instance into a list of edges on the node graph
626
instanceToEdges :: Instance.Instance -> [Graph.Edge]
627
instanceToEdges i
628
  | Instance.hasSecondary i = [(pnode,snode), (snode,pnode)]
629
  | otherwise = []
630
    where pnode = Instance.pNode i
631
          snode = Instance.sNode i
632

    
633
-- | Transform the list of instances into list of destination edges
634
instancesToEdges :: Instance.List -> [Graph.Edge]
635
instancesToEdges = concatMap instanceToEdges . Container.elems
636

    
637
-- | Transform the list of nodes into vertices bounds.
638
-- Returns Nothing is the list is empty.
639
nodesToBounds :: List -> Maybe Graph.Bounds
640
nodesToBounds nl = liftM2 (,) nmin nmax
641
    where nmin = fmap (fst . fst) (IntMap.minViewWithKey nl)
642
          nmax = fmap (fst . fst) (IntMap.maxViewWithKey nl)
643

    
644
-- | The clique of the primary nodes of the instances with a given secondary.
645
-- Return the full graph of those nodes that are primary node of at least one
646
-- instance that has the given node as secondary.
647
nodeToSharedSecondaryEdge :: Instance.List -> Node -> [Graph.Edge]
648
nodeToSharedSecondaryEdge il n = (,) <$> primaries <*> primaries
649
  where primaries = map (Instance.pNode . flip Container.find il) $ sList n
650

    
651

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

    
656
-- | Transform a Node + Instance list into a NodeGraph type.
657
-- Returns Nothing if the node list is empty.
658
mkNodeGraph :: List -> Instance.List -> Maybe Graph.Graph
659
mkNodeGraph nl il =
660
  liftM (`Graph.buildG` (filterValid nl . instancesToEdges $ il))
661
  (nodesToBounds nl)
662

    
663
-- | Transform a Nodes + Instances into a NodeGraph with all reboot exclusions.
664
-- This includes edges between nodes that are the primary nodes of instances
665
-- that have the same secondary node. Nodes not in the node list will not be
666
-- part of the graph, but they are still considered for the edges arising from
667
-- two instances having the same secondary node.
668
-- Return Nothing if the node list is empty.
669
mkRebootNodeGraph :: List -> List -> Instance.List -> Maybe Graph.Graph
670
mkRebootNodeGraph allnodes nl il =
671
  liftM (`Graph.buildG` filterValid nl edges) (nodesToBounds nl)
672
  where
673
    edges = instancesToEdges il `union`
674
            (Container.elems allnodes >>= nodeToSharedSecondaryEdge il) 
675

    
676
-- * Display functions
677

    
678
-- | Return a field for a given node.
679
showField :: Node   -- ^ Node which we're querying
680
          -> String -- ^ Field name
681
          -> String -- ^ Field value as string
682
showField t field =
683
  case field of
684
    "idx"  -> printf "%4d" $ idx t
685
    "name" -> alias t
686
    "fqdn" -> name t
687
    "status" -> case () of
688
                  _ | offline t -> "-"
689
                    | failN1 t -> "*"
690
                    | otherwise -> " "
691
    "tmem" -> printf "%5.0f" $ tMem t
692
    "nmem" -> printf "%5d" $ nMem t
693
    "xmem" -> printf "%5d" $ xMem t
694
    "fmem" -> printf "%5d" $ fMem t
695
    "imem" -> printf "%5d" $ iMem t
696
    "rmem" -> printf "%5d" $ rMem t
697
    "amem" -> printf "%5d" $ fMem t - rMem t
698
    "tdsk" -> printf "%5.0f" $ tDsk t / 1024
699
    "fdsk" -> printf "%5d" $ fDsk t `div` 1024
700
    "tcpu" -> printf "%4.0f" $ tCpu t
701
    "ucpu" -> printf "%4d" $ uCpu t
702
    "pcnt" -> printf "%3d" $ length (pList t)
703
    "scnt" -> printf "%3d" $ length (sList t)
704
    "plist" -> show $ pList t
705
    "slist" -> show $ sList t
706
    "pfmem" -> printf "%6.4f" $ pMem t
707
    "pfdsk" -> printf "%6.4f" $ pDsk t
708
    "rcpu"  -> printf "%5.2f" $ pCpu t
709
    "cload" -> printf "%5.3f" uC
710
    "mload" -> printf "%5.3f" uM
711
    "dload" -> printf "%5.3f" uD
712
    "nload" -> printf "%5.3f" uN
713
    "ptags" -> intercalate "," . map (uncurry (printf "%s=%d")) .
714
               Map.toList $ pTags t
715
    "peermap" -> show $ peers t
716
    "spindle_count" -> show $ tSpindles t
717
    "hi_spindles" -> show $ hiSpindles t
718
    "inst_spindles" -> show $ instSpindles t
719
    _ -> T.unknownField
720
  where
721
    T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
722
                T.dskWeight = uD, T.netWeight = uN } = utilLoad t
723

    
724
-- | Returns the header and numeric propery of a field.
725
showHeader :: String -> (String, Bool)
726
showHeader field =
727
  case field of
728
    "idx" -> ("Index", True)
729
    "name" -> ("Name", False)
730
    "fqdn" -> ("Name", False)
731
    "status" -> ("F", False)
732
    "tmem" -> ("t_mem", True)
733
    "nmem" -> ("n_mem", True)
734
    "xmem" -> ("x_mem", True)
735
    "fmem" -> ("f_mem", True)
736
    "imem" -> ("i_mem", True)
737
    "rmem" -> ("r_mem", True)
738
    "amem" -> ("a_mem", True)
739
    "tdsk" -> ("t_dsk", True)
740
    "fdsk" -> ("f_dsk", True)
741
    "tcpu" -> ("pcpu", True)
742
    "ucpu" -> ("vcpu", True)
743
    "pcnt" -> ("pcnt", True)
744
    "scnt" -> ("scnt", True)
745
    "plist" -> ("primaries", True)
746
    "slist" -> ("secondaries", True)
747
    "pfmem" -> ("p_fmem", True)
748
    "pfdsk" -> ("p_fdsk", True)
749
    "rcpu"  -> ("r_cpu", True)
750
    "cload" -> ("lCpu", True)
751
    "mload" -> ("lMem", True)
752
    "dload" -> ("lDsk", True)
753
    "nload" -> ("lNet", True)
754
    "ptags" -> ("PrimaryTags", False)
755
    "peermap" -> ("PeerMap", False)
756
    "spindle_count" -> ("NodeSpindles", True)
757
    "hi_spindles" -> ("MaxSpindles", True)
758
    "inst_spindles" -> ("InstSpindles", True)
759
    -- TODO: add node fields (group.uuid, group)
760
    _ -> (T.unknownField, False)
761

    
762
-- | String converter for the node list functionality.
763
list :: [String] -> Node -> [String]
764
list fields t = map (showField t) fields
765

    
766
-- | Constant holding the fields we're displaying by default.
767
defaultFields :: [String]
768
defaultFields =
769
  [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
770
  , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
771
  , "pfmem", "pfdsk", "rcpu"
772
  , "cload", "mload", "dload", "nload" ]
773

    
774
{-# ANN computeGroups "HLint: ignore Use alternative" #-}
775
-- | Split a list of nodes into a list of (node group UUID, list of
776
-- associated nodes).
777
computeGroups :: [Node] -> [(T.Gdx, [Node])]
778
computeGroups nodes =
779
  let nodes' = sortBy (comparing group) nodes
780
      nodes'' = groupBy ((==) `on` group) nodes'
781
  -- use of head here is OK, since groupBy returns non-empty lists; if
782
  -- you remove groupBy, also remove use of head
783
  in map (\nl -> (group (head nl), nl)) nodes''