Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Node.hs @ d5072e4c

History | View | Annotate | Download (19.2 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 Google Inc.
10

    
11
This program is free software; you can redistribute it and/or modify
12
it under the terms of the GNU General Public License as published by
13
the Free Software Foundation; either version 2 of the License, or
14
(at your option) any later version.
15

    
16
This program is distributed in the hope that it will be useful, but
17
WITHOUT ANY WARRANTY; without even the implied warranty of
18
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19
General Public License for more details.
20

    
21
You should have received a copy of the GNU General Public License
22
along with this program; if not, write to the Free Software
23
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24
02110-1301, USA.
25

    
26
-}
27

    
28
module Ganeti.HTools.Node
29
    ( Node(..)
30
    , List
31
    -- * Constructor
32
    , create
33
    -- ** Finalization after data loading
34
    , buildPeers
35
    , setIdx
36
    , setAlias
37
    , setOffline
38
    , setXmem
39
    , setFmem
40
    , setPri
41
    , setSec
42
    , setMdsk
43
    , setMcpu
44
    -- * Tag maps
45
    , addTags
46
    , delTags
47
    , rejectAddTags
48
    -- * Instance (re)location
49
    , removePri
50
    , removeSec
51
    , addPri
52
    , addPriEx
53
    , addSec
54
    , addSecEx
55
    -- * Stats
56
    , availDisk
57
    , availMem
58
    , availCpu
59
    , iMem
60
    , iDsk
61
    , conflictingPrimaries
62
    -- * Formatting
63
    , defaultFields
64
    , showHeader
65
    , showField
66
    , list
67
    -- * Misc stuff
68
    , AssocList
69
    , AllocElement
70
    , noSecondary
71
    , computeGroups
72
    ) where
73

    
74
import Data.List hiding (group)
75
import qualified Data.Map as Map
76
import qualified Data.Foldable as Foldable
77
import Data.Ord (comparing)
78
import Text.Printf (printf)
79

    
80
import qualified Ganeti.HTools.Container as Container
81
import qualified Ganeti.HTools.Instance as Instance
82
import qualified Ganeti.HTools.PeerMap as P
83

    
84
import qualified Ganeti.HTools.Types as T
85

    
86
-- * Type declarations
87

    
88
-- | The tag map type
89
type TagMap = Map.Map String Int
90

    
91
-- | The node type.
92
data Node = Node
93
    { name     :: String    -- ^ The node name
94
    , alias    :: String    -- ^ The shortened name (for display purposes)
95
    , tMem     :: Double    -- ^ Total memory (MiB)
96
    , nMem     :: Int       -- ^ Node memory (MiB)
97
    , fMem     :: Int       -- ^ Free memory (MiB)
98
    , xMem     :: Int       -- ^ Unaccounted memory (MiB)
99
    , tDsk     :: Double    -- ^ Total disk space (MiB)
100
    , fDsk     :: Int       -- ^ Free disk space (MiB)
101
    , tCpu     :: Double    -- ^ Total CPU count
102
    , uCpu     :: Int       -- ^ Used VCPU count
103
    , pList    :: [T.Idx]   -- ^ List of primary instance indices
104
    , sList    :: [T.Idx]   -- ^ List of secondary instance indices
105
    , idx      :: T.Ndx     -- ^ Internal index for book-keeping
106
    , peers    :: P.PeerMap -- ^ Pnode to instance mapping
107
    , failN1   :: Bool      -- ^ Whether the node has failed n1
108
    , rMem     :: Int       -- ^ Maximum memory needed for failover by
109
                            -- primaries of this node
110
    , pMem     :: Double    -- ^ Percent of free memory
111
    , pDsk     :: Double    -- ^ Percent of free disk
112
    , pRem     :: Double    -- ^ Percent of reserved memory
113
    , pCpu     :: Double    -- ^ Ratio of virtual to physical CPUs
114
    , mDsk     :: Double    -- ^ Minimum free disk ratio
115
    , mCpu     :: Double    -- ^ Max ratio of virt-to-phys CPUs
116
    , loDsk    :: Int       -- ^ Autocomputed from mDsk low disk
117
                            -- threshold
118
    , hiCpu    :: Int       -- ^ Autocomputed from mCpu high cpu
119
                            -- threshold
120
    , offline  :: Bool      -- ^ Whether the node should not be used
121
                            -- for allocations and skipped from score
122
                            -- computations
123
    , utilPool :: T.DynUtil -- ^ Total utilisation capacity
124
    , utilLoad :: T.DynUtil -- ^ Sum of instance utilisation
125
    , pTags    :: TagMap    -- ^ Map of primary instance tags and their count
126
    , group    :: T.Gdx     -- ^ The node's group (index)
127
    } deriving (Show, Read, Eq)
128

    
129
instance T.Element Node where
130
    nameOf = name
131
    idxOf = idx
132
    setAlias = setAlias
133
    setIdx = setIdx
134
    allNames n = [name n, alias n]
135

    
136
-- | A simple name for the int, node association list.
137
type AssocList = [(T.Ndx, Node)]
138

    
139
-- | A simple name for a node map.
140
type List = Container.Container Node
141

    
142
-- | A simple name for an allocation element (here just for logistic
143
-- reasons)
144
type AllocElement = (List, Instance.Instance, [Node], T.Score)
145

    
146
-- | Constant node index for a non-moveable instance.
147
noSecondary :: T.Ndx
148
noSecondary = -1
149

    
150
-- * Helper functions
151

    
152
-- | Add a tag to a tagmap
153
addTag :: TagMap -> String -> TagMap
154
addTag t s = Map.insertWith (+) s 1 t
155

    
156
-- | Add multiple tags
157
addTags :: TagMap -> [String] -> TagMap
158
addTags = foldl' addTag
159

    
160
-- | Adjust or delete a tag from a tagmap
161
delTag :: TagMap -> String -> TagMap
162
delTag t s = Map.update (\v -> if v > 1
163
                               then Just (v-1)
164
                               else Nothing)
165
             s t
166

    
167
-- | Remove multiple tags
168
delTags :: TagMap -> [String] -> TagMap
169
delTags = foldl' delTag
170

    
171
-- | Check if we can add a list of tags to a tagmap
172
rejectAddTags :: TagMap -> [String] -> Bool
173
rejectAddTags t = any (`Map.member` t)
174

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

    
183
-- * Initialization functions
184

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

    
224
-- | Conversion formula from mDsk\/tDsk to loDsk
225
mDskToloDsk :: Double -> Double -> Int
226
mDskToloDsk mval tdsk = floor (mval * tdsk)
227

    
228
-- | Conversion formula from mCpu\/tCpu to hiCpu
229
mCpuTohiCpu :: Double -> Double -> Int
230
mCpuTohiCpu mval tcpu = floor (mval * tcpu)
231

    
232
-- | Changes the index.
233
--
234
-- This is used only during the building of the data structures.
235
setIdx :: Node -> T.Ndx -> Node
236
setIdx t i = t {idx = i}
237

    
238
-- | Changes the alias.
239
--
240
-- This is used only during the building of the data structures.
241
setAlias :: Node -> String -> Node
242
setAlias t s = t { alias = s }
243

    
244
-- | Sets the offline attribute.
245
setOffline :: Node -> Bool -> Node
246
setOffline t val = t { offline = val }
247

    
248
-- | Sets the unnaccounted memory.
249
setXmem :: Node -> Int -> Node
250
setXmem t val = t { xMem = val }
251

    
252
-- | Sets the max disk usage ratio
253
setMdsk :: Node -> Double -> Node
254
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
255

    
256
-- | Sets the max cpu usage ratio
257
setMcpu :: Node -> Double -> Node
258
setMcpu t val = t { mCpu = val, hiCpu = mCpuTohiCpu val (tCpu t) }
259

    
260
-- | Computes the maximum reserved memory for peers from a peer map.
261
computeMaxRes :: P.PeerMap -> P.Elem
262
computeMaxRes = P.maxElem
263

    
264
-- | Builds the peer map for a given node.
265
buildPeers :: Node -> Instance.List -> Node
266
buildPeers t il =
267
    let mdata = map
268
                (\i_idx -> let inst = Container.find i_idx il
269
                           in (Instance.pNode inst, Instance.mem inst))
270
                (sList t)
271
        pmap = P.accumArray (+) mdata
272
        new_rmem = computeMaxRes pmap
273
        new_failN1 = fMem t <= new_rmem
274
        new_prem = fromIntegral new_rmem / tMem t
275
    in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
276

    
277
-- | Assigns an instance to a node as primary and update the used VCPU
278
-- count, utilisation data and tags map.
279
setPri :: Node -> Instance.Instance -> Node
280
setPri t inst = t { pList = Instance.idx inst:pList t
281
                  , uCpu = new_count
282
                  , pCpu = fromIntegral new_count / tCpu t
283
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
284
                  , pTags = addTags (pTags t) (Instance.tags inst)
285
                  }
286
    where new_count = uCpu t + Instance.vcpus inst
287

    
288
-- | Assigns an instance to a node as secondary without other updates.
289
setSec :: Node -> Instance.Instance -> Node
290
setSec t inst = t { sList = Instance.idx inst:sList t
291
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
292
                                          T.dskWeight (Instance.util inst) }
293
                  }
294
    where old_load = utilLoad t
295

    
296
-- * Update functions
297

    
298
-- | Sets the free memory.
299
setFmem :: Node -> Int -> Node
300
setFmem t new_mem =
301
    let new_n1 = new_mem <= rMem t
302
        new_mp = fromIntegral new_mem / tMem t
303
    in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
304

    
305
-- | Removes a primary instance.
306
removePri :: Node -> Instance.Instance -> Node
307
removePri t inst =
308
    let iname = Instance.idx inst
309
        new_plist = delete iname (pList t)
310
        new_mem = fMem t + Instance.mem inst
311
        new_dsk = fDsk t + Instance.dsk inst
312
        new_mp = fromIntegral new_mem / tMem t
313
        new_dp = fromIntegral new_dsk / tDsk t
314
        new_failn1 = new_mem <= rMem t
315
        new_ucpu = uCpu t - Instance.vcpus inst
316
        new_rcpu = fromIntegral new_ucpu / tCpu t
317
        new_load = utilLoad t `T.subUtil` Instance.util inst
318
    in t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
319
         , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
320
         , uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load
321
         , pTags = delTags (pTags t) (Instance.tags inst) }
322

    
323
-- | Removes a secondary instance.
324
removeSec :: Node -> Instance.Instance -> Node
325
removeSec t inst =
326
    let iname = Instance.idx inst
327
        pnode = Instance.pNode inst
328
        new_slist = delete iname (sList t)
329
        new_dsk = fDsk t + Instance.dsk inst
330
        old_peers = peers t
331
        old_peem = P.find pnode old_peers
332
        new_peem =  old_peem - Instance.mem inst
333
        new_peers = if new_peem > 0
334
                    then P.add pnode new_peem old_peers
335
                    else P.remove pnode old_peers
336
        old_rmem = rMem t
337
        new_rmem = if old_peem < old_rmem
338
                   then old_rmem
339
                   else computeMaxRes new_peers
340
        new_prem = fromIntegral new_rmem / tMem t
341
        new_failn1 = fMem t <= new_rmem
342
        new_dp = fromIntegral new_dsk / tDsk t
343
        old_load = utilLoad t
344
        new_load = old_load { T.dskWeight = T.dskWeight old_load -
345
                                            T.dskWeight (Instance.util inst) }
346
    in t { sList = new_slist, fDsk = new_dsk, peers = new_peers
347
         , failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
348
         , pRem = new_prem, utilLoad = new_load }
349

    
350
-- | Adds a primary instance (basic version).
351
addPri :: Node -> Instance.Instance -> T.OpResult Node
352
addPri = addPriEx False
353

    
354
-- | Adds a primary instance (extended version).
355
addPriEx :: Bool               -- ^ Whether to override the N+1 and
356
                               -- other /soft/ checks, useful if we
357
                               -- come from a worse status
358
                               -- (e.g. offline)
359
         -> Node               -- ^ The target node
360
         -> Instance.Instance  -- ^ The instance to add
361
         -> T.OpResult Node    -- ^ The result of the operation,
362
                               -- either the new version of the node
363
                               -- or a failure mode
364
addPriEx force t inst =
365
    let iname = Instance.idx inst
366
        new_mem = fMem t - Instance.mem inst
367
        new_dsk = fDsk t - Instance.dsk inst
368
        new_failn1 = new_mem <= rMem t
369
        new_ucpu = uCpu t + Instance.vcpus inst
370
        new_pcpu = fromIntegral new_ucpu / tCpu t
371
        new_dp = fromIntegral new_dsk / tDsk t
372
        l_cpu = mCpu t
373
        new_load = utilLoad t `T.addUtil` Instance.util inst
374
        inst_tags = Instance.tags inst
375
        old_tags = pTags t
376
        strict = not force
377
    in case () of
378
         _ | new_mem <= 0 -> T.OpFail T.FailMem
379
           | new_dsk <= 0 -> T.OpFail T.FailDisk
380
           | mDsk t > new_dp && strict -> T.OpFail T.FailDisk
381
           | new_failn1 && not (failN1 t) && strict -> T.OpFail T.FailMem
382
           | l_cpu >= 0 && l_cpu < new_pcpu && strict -> T.OpFail T.FailCPU
383
           | rejectAddTags old_tags inst_tags -> T.OpFail T.FailTags
384
           | otherwise ->
385
               let new_plist = iname:pList t
386
                   new_mp = fromIntegral new_mem / tMem t
387
                   r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
388
                         , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
389
                         , uCpu = new_ucpu, pCpu = new_pcpu
390
                         , utilLoad = new_load
391
                         , pTags = addTags old_tags inst_tags }
392
               in T.OpGood r
393

    
394
-- | Adds a secondary instance (basic version).
395
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
396
addSec = addSecEx False
397

    
398
-- | Adds a secondary instance (extended version).
399
addSecEx :: Bool -> Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
400
addSecEx force t inst pdx =
401
    let iname = Instance.idx inst
402
        old_peers = peers t
403
        old_mem = fMem t
404
        new_dsk = fDsk t - Instance.dsk inst
405
        new_peem = P.find pdx old_peers + Instance.mem inst
406
        new_peers = P.add pdx new_peem old_peers
407
        new_rmem = max (rMem t) new_peem
408
        new_prem = fromIntegral new_rmem / tMem t
409
        new_failn1 = old_mem <= new_rmem
410
        new_dp = fromIntegral new_dsk / tDsk t
411
        old_load = utilLoad t
412
        new_load = old_load { T.dskWeight = T.dskWeight old_load +
413
                                            T.dskWeight (Instance.util inst) }
414
        strict = not force
415
    in case () of
416
         _ | new_dsk <= 0 -> T.OpFail T.FailDisk
417
           | mDsk t > new_dp && strict -> T.OpFail T.FailDisk
418
           | Instance.mem inst >= old_mem && strict -> T.OpFail T.FailMem
419
           | new_failn1 && not (failN1 t) && strict -> T.OpFail T.FailMem
420
           | otherwise ->
421
               let new_slist = iname:sList t
422
                   r = t { sList = new_slist, fDsk = new_dsk
423
                         , peers = new_peers, failN1 = new_failn1
424
                         , rMem = new_rmem, pDsk = new_dp
425
                         , pRem = new_prem, utilLoad = new_load }
426
               in T.OpGood r
427

    
428
-- * Stats functions
429

    
430
-- | Computes the amount of available disk on a given node
431
availDisk :: Node -> Int
432
availDisk t =
433
    let _f = fDsk t
434
        _l = loDsk t
435
    in if _f < _l
436
       then 0
437
       else _f - _l
438

    
439
-- | Computes the amount of used disk on a given node
440
iDsk :: Node -> Int
441
iDsk t = truncate (tDsk t) - fDsk t
442

    
443
-- | Computes the amount of available memory on a given node
444
availMem :: Node -> Int
445
availMem t =
446
    let _f = fMem t
447
        _l = rMem t
448
    in if _f < _l
449
       then 0
450
       else _f - _l
451

    
452
-- | Computes the amount of available memory on a given node
453
availCpu :: Node -> Int
454
availCpu t =
455
    let _u = uCpu t
456
        _l = hiCpu t
457
    in if _l >= _u
458
       then _l - _u
459
       else 0
460

    
461
-- | The memory used by instances on a given node.
462
iMem :: Node -> Int
463
iMem t = truncate (tMem t) - nMem t - xMem t - fMem t
464

    
465
-- * Display functions
466

    
467
showField :: Node -> String -> String
468
showField t field =
469
    case field of
470
      "idx"  -> printf "%4d" $ idx t
471
      "name" -> alias t
472
      "fqdn" -> name t
473
      "status" -> if offline t then "-"
474
                  else if failN1 t then "*" else " "
475
      "tmem" -> printf "%5.0f" $ tMem t
476
      "nmem" -> printf "%5d" $ nMem t
477
      "xmem" -> printf "%5d" $ xMem t
478
      "fmem" -> printf "%5d" $ fMem t
479
      "imem" -> printf "%5d" $ iMem t
480
      "rmem" -> printf "%5d" $ rMem t
481
      "amem" -> printf "%5d" $ fMem t - rMem t
482
      "tdsk" -> printf "%5.0f" $ tDsk t / 1024
483
      "fdsk" -> printf "%5d" $ fDsk t `div` 1024
484
      "tcpu" -> printf "%4.0f" $ tCpu t
485
      "ucpu" -> printf "%4d" $ uCpu t
486
      "pcnt" -> printf "%3d" $ length (pList t)
487
      "scnt" -> printf "%3d" $ length (sList t)
488
      "plist" -> show $ pList t
489
      "slist" -> show $ sList t
490
      "pfmem" -> printf "%6.4f" $ pMem t
491
      "pfdsk" -> printf "%6.4f" $ pDsk t
492
      "rcpu"  -> printf "%5.2f" $ pCpu t
493
      "cload" -> printf "%5.3f" uC
494
      "mload" -> printf "%5.3f" uM
495
      "dload" -> printf "%5.3f" uD
496
      "nload" -> printf "%5.3f" uN
497
      "ptags" -> intercalate "," . map (uncurry (printf "%s=%d")) .
498
                 Map.toList $ pTags t
499
      "peermap" -> show $ peers t
500
      _ -> T.unknownField
501
    where
502
      T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
503
                  T.dskWeight = uD, T.netWeight = uN } = utilLoad t
504

    
505
-- | Returns the header and numeric propery of a field
506
showHeader :: String -> (String, Bool)
507
showHeader field =
508
    case field of
509
      "idx" -> ("Index", True)
510
      "name" -> ("Name", False)
511
      "fqdn" -> ("Name", False)
512
      "status" -> ("F", False)
513
      "tmem" -> ("t_mem", True)
514
      "nmem" -> ("n_mem", True)
515
      "xmem" -> ("x_mem", True)
516
      "fmem" -> ("f_mem", True)
517
      "imem" -> ("i_mem", True)
518
      "rmem" -> ("r_mem", True)
519
      "amem" -> ("a_mem", True)
520
      "tdsk" -> ("t_dsk", True)
521
      "fdsk" -> ("f_dsk", True)
522
      "tcpu" -> ("pcpu", True)
523
      "ucpu" -> ("vcpu", True)
524
      "pcnt" -> ("pcnt", True)
525
      "scnt" -> ("scnt", True)
526
      "plist" -> ("primaries", True)
527
      "slist" -> ("secondaries", True)
528
      "pfmem" -> ("p_fmem", True)
529
      "pfdsk" -> ("p_fdsk", True)
530
      "rcpu"  -> ("r_cpu", True)
531
      "cload" -> ("lCpu", True)
532
      "mload" -> ("lMem", True)
533
      "dload" -> ("lDsk", True)
534
      "nload" -> ("lNet", True)
535
      "ptags" -> ("PrimaryTags", False)
536
      "peermap" -> ("PeerMap", False)
537
      -- TODO: add node fields (group.uuid, group)
538
      _ -> (T.unknownField, False)
539

    
540
-- | String converter for the node list functionality.
541
list :: [String] -> Node -> [String]
542
list fields t = map (showField t) fields
543

    
544

    
545
defaultFields :: [String]
546
defaultFields =
547
    [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
548
    , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
549
    , "pfmem", "pfdsk", "rcpu"
550
    , "cload", "mload", "dload", "nload" ]
551

    
552
-- | Split a list of nodes into a list of (node group UUID, list of
553
-- associated nodes)
554
computeGroups :: [Node] -> [(T.Gdx, [Node])]
555
computeGroups nodes =
556
  let nodes' = sortBy (comparing group) nodes
557
      nodes'' = groupBy (\a b -> group a == group b) nodes'
558
  in map (\nl -> (group (head nl), nl)) nodes''