Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Node.hs @ b3fc101f

History | View | Annotate | Download (29.1 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
  , setCpuSpeed
48
  -- * Tag maps
49
  , addTags
50
  , delTags
51
  , rejectAddTags
52
  -- * Instance (re)location
53
  , removePri
54
  , removeSec
55
  , addPri
56
  , addPriEx
57
  , addSec
58
  , addSecEx
59
  -- * Stats
60
  , availDisk
61
  , availMem
62
  , availCpu
63
  , iMem
64
  , iDsk
65
  , conflictingPrimaries
66
  -- * Formatting
67
  , defaultFields
68
  , showHeader
69
  , showField
70
  , list
71
  -- * Misc stuff
72
  , AssocList
73
  , AllocElement
74
  , noSecondary
75
  , computeGroups
76
  , mkNodeGraph
77
  , mkRebootNodeGraph
78
  , haveExclStorage
79
  ) where
80

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

    
92
import qualified Ganeti.HTools.Container as Container
93
import qualified Ganeti.HTools.Instance as Instance
94
import qualified Ganeti.HTools.PeerMap as P
95

    
96
import Ganeti.BasicTypes
97
import qualified Ganeti.HTools.Types as T
98

    
99
-- * Type declarations
100

    
101
-- | The tag map type.
102
type TagMap = Map.Map String Int
103

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

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

    
163
instance T.Element Node where
164
  nameOf = name
165
  idxOf = idx
166
  setAlias = setAlias
167
  setIdx = setIdx
168
  allNames n = [name n, alias n]
169

    
170
-- | A simple name for the int, node association list.
171
type AssocList = [(T.Ndx, Node)]
172

    
173
-- | A simple name for a node map.
174
type List = Container.Container Node
175

    
176
-- | A simple name for an allocation element (here just for logistic
177
-- reasons).
178
type AllocElement = (List, Instance.Instance, [Node], T.Score)
179

    
180
-- | Constant node index for a non-moveable instance.
181
noSecondary :: T.Ndx
182
noSecondary = -1
183

    
184
-- * Helper functions
185

    
186
-- | Add a tag to a tagmap.
187
addTag :: TagMap -> String -> TagMap
188
addTag t s = Map.insertWith (+) s 1 t
189

    
190
-- | Add multiple tags.
191
addTags :: TagMap -> [String] -> TagMap
192
addTags = foldl' addTag
193

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

    
201
-- | Remove multiple tags.
202
delTags :: TagMap -> [String] -> TagMap
203
delTags = foldl' delTag
204

    
205
-- | Check if we can add a list of tags to a tagmap.
206
rejectAddTags :: TagMap -> [String] -> Bool
207
rejectAddTags t = any (`Map.member` t)
208

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

    
217
-- | Helper function to increment a base value depending on the passed
218
-- boolean argument.
219
incIf :: (Num a) => Bool -> a -> a -> a
220
incIf True  base delta = base + delta
221
incIf False base _     = base
222

    
223
-- | Helper function to decrement a base value depending on the passed
224
-- boolean argument.
225
decIf :: (Num a) => Bool -> a -> a -> a
226
decIf True  base delta = base - delta
227
decIf False base _     = base
228

    
229
-- | Is exclusive storage enabled on any node?
230
haveExclStorage :: List -> Bool
231
haveExclStorage nl =
232
  any exclStorage $ Container.elems nl
233

    
234
-- * Initialization functions
235

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

    
290
-- | Conversion formula from mDsk\/tDsk to loDsk.
291
mDskToloDsk :: Double -> Double -> Int
292
mDskToloDsk mval = floor . (mval *)
293

    
294
-- | Conversion formula from mCpu\/tCpu to hiCpu.
295
mCpuTohiCpu :: Double -> Double -> Int
296
mCpuTohiCpu mval = floor . (mval *)
297

    
298
-- | Conversiojn formula from spindles and spindle ratio to hiSpindles.
299
computeHiSpindles :: Double -> Int -> Double
300
computeHiSpindles spindle_ratio = (spindle_ratio *) . fromIntegral
301

    
302
-- | Changes the index.
303
--
304
-- This is used only during the building of the data structures.
305
setIdx :: Node -> T.Ndx -> Node
306
setIdx t i = t {idx = i}
307

    
308
-- | Changes the alias.
309
--
310
-- This is used only during the building of the data structures.
311
setAlias :: Node -> String -> Node
312
setAlias t s = t { alias = s }
313

    
314
-- | Sets the offline attribute.
315
setOffline :: Node -> Bool -> Node
316
setOffline t val = t { offline = val }
317

    
318
-- | Sets the master attribute
319
setMaster :: Node -> Bool -> Node
320
setMaster t val = t { isMaster = val }
321

    
322
-- | Sets the node tags attribute
323
setNodeTags :: Node -> [String] -> Node
324
setNodeTags t val = t { nTags = val }
325

    
326
-- | Sets the unnaccounted memory.
327
setXmem :: Node -> Int -> Node
328
setXmem t val = t { xMem = val }
329

    
330
-- | Sets the max disk usage ratio.
331
setMdsk :: Node -> Double -> Node
332
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
333

    
334
-- | Sets the max cpu usage ratio. This will update the node's
335
-- ipolicy, losing sharing (but it should be a seldomly done operation).
336
setMcpu :: Node -> Double -> Node
337
setMcpu t val =
338
  let new_ipol = (iPolicy t) { T.iPolicyVcpuRatio = val }
339
  in t { hiCpu = mCpuTohiCpu val (tCpu t), iPolicy = new_ipol }
340

    
341
-- | Sets the policy.
342
setPolicy :: T.IPolicy -> Node -> Node
343
setPolicy pol node =
344
  node { iPolicy = pol
345
       , hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio pol) (tCpu node)
346
       , hiSpindles = computeHiSpindles (T.iPolicySpindleRatio pol)
347
                      (tSpindles node)
348
       }
349

    
350
-- | Computes the maximum reserved memory for peers from a peer map.
351
computeMaxRes :: P.PeerMap -> P.Elem
352
computeMaxRes = P.maxElem
353

    
354
-- | Builds the peer map for a given node.
355
buildPeers :: Node -> Instance.List -> Node
356
buildPeers t il =
357
  let mdata = map
358
              (\i_idx -> let inst = Container.find i_idx il
359
                             mem = if Instance.usesSecMem inst
360
                                     then Instance.mem inst
361
                                     else 0
362
                         in (Instance.pNode inst, mem))
363
              (sList t)
364
      pmap = P.accumArray (+) mdata
365
      new_rmem = computeMaxRes pmap
366
      new_failN1 = fMem t <= new_rmem
367
      new_prem = fromIntegral new_rmem / tMem t
368
  in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
369

    
370
-- | Calculate the new spindle usage
371
calcSpindleUse ::
372
                  Bool -- Action: True = adding instance, False = removing it
373
               -> Node -> Instance.Instance -> Double
374
calcSpindleUse _ (Node {exclStorage = True}) _ = 0.0
375
calcSpindleUse act n@(Node {exclStorage = False}) i =
376
  f (Instance.usesLocalStorage i) (instSpindles n)
377
    (fromIntegral $ Instance.spindleUse i)
378
    where
379
      f :: Bool -> Double -> Double -> Double -- avoid monomorphism restriction
380
      f = if act then incIf else decIf
381

    
382
-- | Calculate the new number of free spindles
383
calcNewFreeSpindles ::
384
                       Bool -- Action: True = adding instance, False = removing
385
                    -> Node -> Instance.Instance -> Int
386
calcNewFreeSpindles _ (Node {exclStorage = False}) _ = 0
387
calcNewFreeSpindles act n@(Node {exclStorage = True}) i =
388
  case Instance.getTotalSpindles i of
389
    Nothing -> if act
390
               then -1 -- Force a spindle error, so the instance don't go here
391
               else fSpindles n -- No change, as we aren't sure
392
    Just s -> (if act then (-) else (+)) (fSpindles n) s
393

    
394
-- | Assigns an instance to a node as primary and update the used VCPU
395
-- count, utilisation data and tags map.
396
setPri :: Node -> Instance.Instance -> Node
397
setPri t inst = t { pList = Instance.idx inst:pList t
398
                  , uCpu = new_count
399
                  , pCpu = fromIntegral new_count / tCpu t
400
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
401
                  , pTags = addTags (pTags t) (Instance.exclTags inst)
402
                  , instSpindles = calcSpindleUse True t inst
403
                  }
404
  where new_count = Instance.applyIfOnline inst (+ Instance.vcpus inst)
405
                    (uCpu t )
406

    
407
-- | Assigns an instance to a node as secondary and updates disk utilisation.
408
setSec :: Node -> Instance.Instance -> Node
409
setSec t inst = t { sList = Instance.idx inst:sList t
410
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
411
                                          T.dskWeight (Instance.util inst) }
412
                  , instSpindles = calcSpindleUse True t inst
413
                  }
414
  where old_load = utilLoad t
415

    
416
-- | Computes the new 'pDsk' value, handling nodes without local disk
417
-- storage (we consider all their disk unused).
418
computePDsk :: Int -> Double -> Double
419
computePDsk _    0     = 1
420
computePDsk free total = fromIntegral free / total
421

    
422
-- | Computes the new 'pDsk' value, handling the exclusive storage state.
423
computeNewPDsk :: Node -> Int -> Int -> Double
424
computeNewPDsk node new_free_sp new_free_dsk =
425
  if exclStorage node
426
  then computePDsk new_free_sp . fromIntegral $ tSpindles node
427
  else computePDsk new_free_dsk $ tDsk node
428

    
429
-- * Update functions
430

    
431
-- | Set the CPU speed
432
setCpuSpeed :: Node -> Double -> Node
433
setCpuSpeed n f = n { tCpuSpeed = f }
434

    
435
-- | Sets the free memory.
436
setFmem :: Node -> Int -> Node
437
setFmem t new_mem =
438
  let new_n1 = new_mem < rMem t
439
      new_mp = fromIntegral new_mem / tMem t
440
  in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
441

    
442
-- | Removes a primary instance.
443
removePri :: Node -> Instance.Instance -> Node
444
removePri t inst =
445
  let iname = Instance.idx inst
446
      i_online = Instance.notOffline inst
447
      uses_disk = Instance.usesLocalStorage inst
448
      new_plist = delete iname (pList t)
449
      new_mem = incIf i_online (fMem t) (Instance.mem inst)
450
      new_dsk = incIf uses_disk (fDsk t) (Instance.dsk inst)
451
      new_free_sp = calcNewFreeSpindles False t inst
452
      new_inst_sp = calcSpindleUse False t inst
453
      new_mp = fromIntegral new_mem / tMem t
454
      new_dp = computeNewPDsk t new_free_sp new_dsk
455
      new_failn1 = new_mem <= rMem t
456
      new_ucpu = decIf i_online (uCpu t) (Instance.vcpus inst)
457
      new_rcpu = fromIntegral new_ucpu / tCpu t
458
      new_load = utilLoad t `T.subUtil` Instance.util inst
459
  in t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
460
       , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
461
       , uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load
462
       , pTags = delTags (pTags t) (Instance.exclTags inst)
463
       , instSpindles = new_inst_sp, fSpindles = new_free_sp
464
       }
465

    
466
-- | Removes a secondary instance.
467
removeSec :: Node -> Instance.Instance -> Node
468
removeSec t inst =
469
  let iname = Instance.idx inst
470
      uses_disk = Instance.usesLocalStorage inst
471
      cur_dsk = fDsk t
472
      pnode = Instance.pNode inst
473
      new_slist = delete iname (sList t)
474
      new_dsk = incIf uses_disk cur_dsk (Instance.dsk inst)
475
      new_free_sp = calcNewFreeSpindles False t inst
476
      new_inst_sp = calcSpindleUse False t inst
477
      old_peers = peers t
478
      old_peem = P.find pnode old_peers
479
      new_peem = decIf (Instance.usesSecMem inst) old_peem (Instance.mem inst)
480
      new_peers = if new_peem > 0
481
                    then P.add pnode new_peem old_peers
482
                    else P.remove pnode old_peers
483
      old_rmem = rMem t
484
      new_rmem = if old_peem < old_rmem
485
                   then old_rmem
486
                   else computeMaxRes new_peers
487
      new_prem = fromIntegral new_rmem / tMem t
488
      new_failn1 = fMem t <= new_rmem
489
      new_dp = computeNewPDsk t new_free_sp new_dsk
490
      old_load = utilLoad t
491
      new_load = old_load { T.dskWeight = T.dskWeight old_load -
492
                                          T.dskWeight (Instance.util inst) }
493
  in t { sList = new_slist, fDsk = new_dsk, peers = new_peers
494
       , failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
495
       , pRem = new_prem, utilLoad = new_load
496
       , instSpindles = new_inst_sp, fSpindles = new_free_sp
497
       }
498

    
499
-- | Adds a primary instance (basic version).
500
addPri :: Node -> Instance.Instance -> T.OpResult Node
501
addPri = addPriEx False
502

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

    
553
-- | Adds a secondary instance (basic version).
554
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
555
addSec = addSecEx False
556

    
557
-- | Adds a secondary instance (extended version).
558
addSecEx :: Bool -> Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
559
addSecEx force t inst pdx =
560
  let iname = Instance.idx inst
561
      old_peers = peers t
562
      old_mem = fMem t
563
      new_dsk = fDsk t - Instance.dsk inst
564
      new_free_sp = calcNewFreeSpindles True t inst
565
      new_inst_sp = calcSpindleUse True t inst
566
      secondary_needed_mem = if Instance.usesSecMem inst
567
                               then Instance.mem inst
568
                               else 0
569
      new_peem = P.find pdx old_peers + secondary_needed_mem
570
      new_peers = P.add pdx new_peem old_peers
571
      new_rmem = max (rMem t) new_peem
572
      new_prem = fromIntegral new_rmem / tMem t
573
      new_failn1 = old_mem <= new_rmem
574
      new_dp = computeNewPDsk t new_free_sp new_dsk
575
      old_load = utilLoad t
576
      new_load = old_load { T.dskWeight = T.dskWeight old_load +
577
                                          T.dskWeight (Instance.util inst) }
578
      strict = not force
579
  in case () of
580
       _ | not (Instance.hasSecondary inst) -> Bad T.FailDisk
581
         | new_dsk <= 0 -> Bad T.FailDisk
582
         | new_dsk < loDsk t && strict -> Bad T.FailDisk
583
         | exclStorage t && new_free_sp < 0 -> Bad T.FailSpindles
584
         | new_inst_sp > hiSpindles t && strict -> Bad T.FailDisk
585
         | secondary_needed_mem >= old_mem && strict -> Bad T.FailMem
586
         | new_failn1 && not (failN1 t) && strict -> Bad T.FailMem
587
         | otherwise ->
588
           let new_slist = iname:sList t
589
               r = t { sList = new_slist, fDsk = new_dsk
590
                     , peers = new_peers, failN1 = new_failn1
591
                     , rMem = new_rmem, pDsk = new_dp
592
                     , pRem = new_prem, utilLoad = new_load
593
                     , instSpindles = new_inst_sp
594
                     , fSpindles = new_free_sp
595
                     }
596
           in Ok r
597

    
598
-- * Stats functions
599

    
600
-- | Computes the amount of available disk on a given node.
601
availDisk :: Node -> Int
602
availDisk t =
603
  let _f = fDsk t
604
      _l = loDsk t
605
  in if _f < _l
606
       then 0
607
       else _f - _l
608

    
609
-- | Computes the amount of used disk on a given node.
610
iDsk :: Node -> Int
611
iDsk t = truncate (tDsk t) - fDsk t
612

    
613
-- | Computes the amount of available memory on a given node.
614
availMem :: Node -> Int
615
availMem t =
616
  let _f = fMem t
617
      _l = rMem t
618
  in if _f < _l
619
       then 0
620
       else _f - _l
621

    
622
-- | Computes the amount of available memory on a given node.
623
availCpu :: Node -> Int
624
availCpu t =
625
  let _u = uCpu t
626
      _l = hiCpu t
627
  in if _l >= _u
628
       then _l - _u
629
       else 0
630

    
631
-- | The memory used by instances on a given node.
632
iMem :: Node -> Int
633
iMem t = truncate (tMem t) - nMem t - xMem t - fMem t
634

    
635
-- * Node graph functions
636
-- These functions do the transformations needed so that nodes can be
637
-- represented as a graph connected by the instances that are replicated
638
-- on them.
639

    
640
-- * Making of a Graph from a node/instance list
641

    
642
-- | Transform an instance into a list of edges on the node graph
643
instanceToEdges :: Instance.Instance -> [Graph.Edge]
644
instanceToEdges i
645
  | Instance.hasSecondary i = [(pnode,snode), (snode,pnode)]
646
  | otherwise = []
647
    where pnode = Instance.pNode i
648
          snode = Instance.sNode i
649

    
650
-- | Transform the list of instances into list of destination edges
651
instancesToEdges :: Instance.List -> [Graph.Edge]
652
instancesToEdges = concatMap instanceToEdges . Container.elems
653

    
654
-- | Transform the list of nodes into vertices bounds.
655
-- Returns Nothing is the list is empty.
656
nodesToBounds :: List -> Maybe Graph.Bounds
657
nodesToBounds nl = liftM2 (,) nmin nmax
658
    where nmin = fmap (fst . fst) (IntMap.minViewWithKey nl)
659
          nmax = fmap (fst . fst) (IntMap.maxViewWithKey nl)
660

    
661
-- | The clique of the primary nodes of the instances with a given secondary.
662
-- Return the full graph of those nodes that are primary node of at least one
663
-- instance that has the given node as secondary.
664
nodeToSharedSecondaryEdge :: Instance.List -> Node -> [Graph.Edge]
665
nodeToSharedSecondaryEdge il n = (,) <$> primaries <*> primaries
666
  where primaries = map (Instance.pNode . flip Container.find il) $ sList n
667

    
668

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

    
673
-- | Transform a Node + Instance list into a NodeGraph type.
674
-- Returns Nothing if the node list is empty.
675
mkNodeGraph :: List -> Instance.List -> Maybe Graph.Graph
676
mkNodeGraph nl il =
677
  liftM (`Graph.buildG` (filterValid nl . instancesToEdges $ il))
678
  (nodesToBounds nl)
679

    
680
-- | Transform a Nodes + Instances into a NodeGraph with all reboot exclusions.
681
-- This includes edges between nodes that are the primary nodes of instances
682
-- that have the same secondary node. Nodes not in the node list will not be
683
-- part of the graph, but they are still considered for the edges arising from
684
-- two instances having the same secondary node.
685
-- Return Nothing if the node list is empty.
686
mkRebootNodeGraph :: List -> List -> Instance.List -> Maybe Graph.Graph
687
mkRebootNodeGraph allnodes nl il =
688
  liftM (`Graph.buildG` filterValid nl edges) (nodesToBounds nl)
689
  where
690
    edges = instancesToEdges il `union`
691
            (Container.elems allnodes >>= nodeToSharedSecondaryEdge il) 
692

    
693
-- * Display functions
694

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

    
741
-- | Returns the header and numeric propery of a field.
742
showHeader :: String -> (String, Bool)
743
showHeader field =
744
  case field of
745
    "idx" -> ("Index", True)
746
    "name" -> ("Name", False)
747
    "fqdn" -> ("Name", False)
748
    "status" -> ("F", False)
749
    "tmem" -> ("t_mem", True)
750
    "nmem" -> ("n_mem", True)
751
    "xmem" -> ("x_mem", True)
752
    "fmem" -> ("f_mem", True)
753
    "imem" -> ("i_mem", True)
754
    "rmem" -> ("r_mem", True)
755
    "amem" -> ("a_mem", True)
756
    "tdsk" -> ("t_dsk", True)
757
    "fdsk" -> ("f_dsk", True)
758
    "tcpu" -> ("pcpu", True)
759
    "ucpu" -> ("vcpu", True)
760
    "pcnt" -> ("pcnt", True)
761
    "scnt" -> ("scnt", True)
762
    "plist" -> ("primaries", True)
763
    "slist" -> ("secondaries", True)
764
    "pfmem" -> ("p_fmem", True)
765
    "pfdsk" -> ("p_fdsk", True)
766
    "rcpu"  -> ("r_cpu", True)
767
    "cload" -> ("lCpu", True)
768
    "mload" -> ("lMem", True)
769
    "dload" -> ("lDsk", True)
770
    "nload" -> ("lNet", True)
771
    "ptags" -> ("PrimaryTags", False)
772
    "peermap" -> ("PeerMap", False)
773
    "spindle_count" -> ("NodeSpindles", True)
774
    "hi_spindles" -> ("MaxSpindles", True)
775
    "inst_spindles" -> ("InstSpindles", True)
776
    -- TODO: add node fields (group.uuid, group)
777
    _ -> (T.unknownField, False)
778

    
779
-- | String converter for the node list functionality.
780
list :: [String] -> Node -> [String]
781
list fields t = map (showField t) fields
782

    
783
-- | Constant holding the fields we're displaying by default.
784
defaultFields :: [String]
785
defaultFields =
786
  [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
787
  , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
788
  , "pfmem", "pfdsk", "rcpu"
789
  , "cload", "mload", "dload", "nload" ]
790

    
791
{-# ANN computeGroups "HLint: ignore Use alternative" #-}
792
-- | Split a list of nodes into a list of (node group UUID, list of
793
-- associated nodes).
794
computeGroups :: [Node] -> [(T.Gdx, [Node])]
795
computeGroups nodes =
796
  let nodes' = sortBy (comparing group) nodes
797
      nodes'' = groupBy ((==) `on` group) nodes'
798
  -- use of head here is OK, since groupBy returns non-empty lists; if
799
  -- you remove groupBy, also remove use of head
800
  in map (\nl -> (group (head nl), nl)) nodes''