Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ c4d98278

History | View | Annotate | Download (18.7 kB)

1
{-| Module describing a node.
2

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

    
7
{-
8

    
9
Copyright (C) 2009, 2010 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
    , conflictingPrimaries
60
    -- * Formatting
61
    , defaultFields
62
    , showHeader
63
    , showField
64
    , list
65
    -- * Misc stuff
66
    , AssocList
67
    , AllocElement
68
    , noSecondary
69
    ) where
70

    
71
import Data.List hiding (group)
72
import qualified Data.Map as Map
73
import qualified Data.Foldable as Foldable
74
import Text.Printf (printf)
75

    
76
import qualified Ganeti.HTools.Container as Container
77
import qualified Ganeti.HTools.Instance as Instance
78
import qualified Ganeti.HTools.PeerMap as P
79

    
80
import qualified Ganeti.HTools.Types as T
81

    
82
-- * Type declarations
83

    
84
-- | The tag map type
85
type TagMap = Map.Map String Int
86

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

    
125
instance T.Element Node where
126
    nameOf = name
127
    idxOf = idx
128
    setAlias = setAlias
129
    setIdx = setIdx
130
    allNames n = [name n, alias n]
131

    
132
-- | A simple name for the int, node association list.
133
type AssocList = [(T.Ndx, Node)]
134

    
135
-- | A simple name for a node map.
136
type List = Container.Container Node
137

    
138
-- | A simple name for an allocation element (here just for logistic
139
-- reasons)
140
type AllocElement = (List, Instance.Instance, [Node])
141

    
142
-- | Constant node index for a non-moveable instance.
143
noSecondary :: T.Ndx
144
noSecondary = -1
145

    
146
-- * Helper functions
147

    
148
-- | Add a tag to a tagmap
149
addTag :: TagMap -> String -> TagMap
150
addTag t s = Map.insertWith (+) s 1 t
151

    
152
-- | Add multiple tags
153
addTags :: TagMap -> [String] -> TagMap
154
addTags = foldl' addTag
155

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

    
163
-- | Remove multiple tags
164
delTags :: TagMap -> [String] -> TagMap
165
delTags = foldl' delTag
166

    
167
-- | Check if we can add a list of tags to a tagmap
168
rejectAddTags :: TagMap -> [String] -> Bool
169
rejectAddTags t = any (`Map.member` t)
170

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

    
179
-- * Initialization functions
180

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

    
220
-- | Conversion formula from mDsk\/tDsk to loDsk
221
mDskToloDsk :: Double -> Double -> Int
222
mDskToloDsk mval tdsk = floor (mval * tdsk)
223

    
224
-- | Conversion formula from mCpu\/tCpu to hiCpu
225
mCpuTohiCpu :: Double -> Double -> Int
226
mCpuTohiCpu mval tcpu = floor (mval * tcpu)
227

    
228
-- | Changes the index.
229
--
230
-- This is used only during the building of the data structures.
231
setIdx :: Node -> T.Ndx -> Node
232
setIdx t i = t {idx = i}
233

    
234
-- | Changes the alias.
235
--
236
-- This is used only during the building of the data structures.
237
setAlias :: Node -> String -> Node
238
setAlias t s = t { alias = s }
239

    
240
-- | Sets the offline attribute.
241
setOffline :: Node -> Bool -> Node
242
setOffline t val = t { offline = val }
243

    
244
-- | Sets the unnaccounted memory.
245
setXmem :: Node -> Int -> Node
246
setXmem t val = t { xMem = val }
247

    
248
-- | Sets the max disk usage ratio
249
setMdsk :: Node -> Double -> Node
250
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
251

    
252
-- | Sets the max cpu usage ratio
253
setMcpu :: Node -> Double -> Node
254
setMcpu t val = t { mCpu = val, hiCpu = mCpuTohiCpu val (tCpu t) }
255

    
256
-- | Computes the maximum reserved memory for peers from a peer map.
257
computeMaxRes :: P.PeerMap -> P.Elem
258
computeMaxRes = P.maxElem
259

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

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

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

    
292
-- * Update functions
293

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

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

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

    
346
-- | Adds a primary instance (basic version).
347
addPri :: Node -> Instance.Instance -> T.OpResult Node
348
addPri = addPriEx False
349

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

    
390
-- | Adds a secondary instance (basic version).
391
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
392
addSec = addSecEx False
393

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

    
424
-- * Stats functions
425

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

    
435
-- | Computes the amount of available memory on a given node
436
availMem :: Node -> Int
437
availMem t =
438
    let _f = fMem t
439
        _l = rMem t
440
    in if _f < _l
441
       then 0
442
       else _f - _l
443

    
444
-- | Computes the amount of available memory on a given node
445
availCpu :: Node -> Int
446
availCpu t =
447
    let _u = uCpu t
448
        _l = hiCpu t
449
    in if _l >= _u
450
       then _l - _u
451
       else 0
452

    
453
-- * Display functions
454

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

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

    
530
-- | String converter for the node list functionality.
531
list :: [String] -> Node -> [String]
532
list fields t = map (showField t) fields
533

    
534

    
535
defaultFields :: [String]
536
defaultFields =
537
    [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
538
    , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
539
    , "pfmem", "pfdsk", "rcpu"
540
    , "cload", "mload", "dload", "nload" ]