Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ 3ed46bb7

History | View | Annotate | Download (16.9 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 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
    , setName
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
    , addSec
53
    -- * Stats
54
    , availDisk
55
    , availMem
56
    , availCpu
57
    , conflictingPrimaries
58
    -- * Formatting
59
    , defaultFields
60
    , showHeader
61
    , showField
62
    , list
63
    -- * Misc stuff
64
    , AssocList
65
    , AllocElement
66
    , noSecondary
67
    ) where
68

    
69
import Data.List
70
import qualified Data.Map as Map
71
import qualified Data.Foldable as Foldable
72
import Text.Printf (printf)
73

    
74
import qualified Ganeti.HTools.Container as Container
75
import qualified Ganeti.HTools.Instance as Instance
76
import qualified Ganeti.HTools.PeerMap as P
77

    
78
import qualified Ganeti.HTools.Types as T
79

    
80
-- * Type declarations
81

    
82
-- | The tag map type
83
type TagMap = Map.Map String Int
84

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

    
121
instance T.Element Node where
122
    nameOf = name
123
    idxOf = idx
124
    setName = setName
125
    setIdx = setIdx
126

    
127
-- | A simple name for the int, node association list.
128
type AssocList = [(T.Ndx, Node)]
129

    
130
-- | A simple name for a node map.
131
type List = Container.Container Node
132

    
133
-- | A simple name for an allocation element (here just for logistic
134
-- reasons)
135
type AllocElement = (List, Instance.Instance, [Node])
136

    
137
-- | Constant node index for a non-moveable instance.
138
noSecondary :: T.Ndx
139
noSecondary = -1
140

    
141
-- * Helper functions
142

    
143
-- | Add a tag to a tagmap
144
addTag :: TagMap -> String -> TagMap
145
addTag t s = Map.insertWith (+) s 1 t
146

    
147
-- | Add multiple tags
148
addTags :: TagMap -> [String] -> TagMap
149
addTags = foldl' addTag
150

    
151
-- | Adjust or delete a tag from a tagmap
152
delTag :: TagMap -> String -> TagMap
153
delTag t s = Map.update (\v -> if v > 1
154
                               then Just (v-1)
155
                               else Nothing)
156
             s t
157

    
158
-- | Remove multiple tags
159
delTags :: TagMap -> [String] -> TagMap
160
delTags = foldl' delTag
161

    
162
-- | Check if we can add a list of tags to a tagmap
163
rejectAddTags :: TagMap -> [String] -> Bool
164
rejectAddTags t = any (`Map.member` t)
165

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

    
174
-- * Initialization functions
175

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

    
213
-- | Conversion formula from mDsk\/tDsk to loDsk
214
mDskToloDsk :: Double -> Double -> Int
215
mDskToloDsk mval tdsk = floor (mval * tdsk)
216

    
217
-- | Conversion formula from mCpu\/tCpu to hiCpu
218
mCpuTohiCpu :: Double -> Double -> Int
219
mCpuTohiCpu mval tcpu = floor (mval * tcpu)
220

    
221
-- | Changes the index.
222
--
223
-- This is used only during the building of the data structures.
224
setIdx :: Node -> T.Ndx -> Node
225
setIdx t i = t {idx = i}
226

    
227
-- | Changes the name.
228
--
229
-- This is used only during the building of the data structures.
230
setName :: Node -> String -> Node
231
setName t s = t {name = s}
232

    
233
-- | Sets the offline attribute.
234
setOffline :: Node -> Bool -> Node
235
setOffline t val = t { offline = val }
236

    
237
-- | Sets the unnaccounted memory.
238
setXmem :: Node -> Int -> Node
239
setXmem t val = t { xMem = val }
240

    
241
-- | Sets the max disk usage ratio
242
setMdsk :: Node -> Double -> Node
243
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
244

    
245
-- | Sets the max cpu usage ratio
246
setMcpu :: Node -> Double -> Node
247
setMcpu t val = t { mCpu = val, hiCpu = mCpuTohiCpu val (tCpu t) }
248

    
249
-- | Computes the maximum reserved memory for peers from a peer map.
250
computeMaxRes :: P.PeerMap -> P.Elem
251
computeMaxRes = P.maxElem
252

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

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

    
277
-- | Assigns an instance to a node as secondary without other updates.
278
setSec :: Node -> Instance.Instance -> Node
279
setSec t inst = t { sList = Instance.idx inst:sList t
280
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
281
                                          T.dskWeight (Instance.util inst) }
282
                  }
283
    where old_load = utilLoad t
284

    
285
-- * Update functions
286

    
287
-- | Sets the free memory.
288
setFmem :: Node -> Int -> Node
289
setFmem t new_mem =
290
    let new_n1 = new_mem <= rMem t
291
        new_mp = fromIntegral new_mem / tMem t
292
    in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
293

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

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

    
337
-- | Adds a primary instance.
338
addPri :: Node -> Instance.Instance -> T.OpResult Node
339
addPri t inst =
340
    let iname = Instance.idx inst
341
        new_mem = fMem t - Instance.mem inst
342
        new_dsk = fDsk t - Instance.dsk inst
343
        new_failn1 = new_mem <= rMem t
344
        new_ucpu = uCpu t + Instance.vcpus inst
345
        new_pcpu = fromIntegral new_ucpu / tCpu t
346
        new_dp = fromIntegral new_dsk / tDsk t
347
        l_cpu = mCpu t
348
        new_load = utilLoad t `T.addUtil` Instance.util inst
349
        inst_tags = Instance.tags inst
350
        old_tags = pTags t
351
    in case () of
352
         _ | new_mem <= 0 -> T.OpFail T.FailMem
353
           | new_dsk <= 0 || mDsk t > new_dp -> T.OpFail T.FailDisk
354
           | new_failn1 && not (failN1 t) -> T.OpFail T.FailMem
355
           | l_cpu >= 0 && l_cpu < new_pcpu -> T.OpFail T.FailCPU
356
           | rejectAddTags old_tags inst_tags -> T.OpFail T.FailTags
357
           | otherwise ->
358
               let new_plist = iname:pList t
359
                   new_mp = fromIntegral new_mem / tMem t
360
                   r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
361
                         , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
362
                         , uCpu = new_ucpu, pCpu = new_pcpu
363
                         , utilLoad = new_load
364
                         , pTags = addTags old_tags inst_tags }
365
               in T.OpGood r
366

    
367
-- | Adds a secondary instance.
368
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
369
addSec t inst pdx =
370
    let iname = Instance.idx inst
371
        old_peers = peers t
372
        old_mem = fMem t
373
        new_dsk = fDsk t - Instance.dsk inst
374
        new_peem = P.find pdx old_peers + Instance.mem inst
375
        new_peers = P.add pdx new_peem old_peers
376
        new_rmem = max (rMem t) new_peem
377
        new_prem = fromIntegral new_rmem / tMem t
378
        new_failn1 = old_mem <= new_rmem
379
        new_dp = fromIntegral new_dsk / tDsk t
380
        old_load = utilLoad t
381
        new_load = old_load { T.dskWeight = T.dskWeight old_load +
382
                                            T.dskWeight (Instance.util inst) }
383
    in case () of
384
         _ | new_dsk <= 0 || mDsk t > new_dp -> T.OpFail T.FailDisk
385
           | Instance.mem inst >= old_mem -> T.OpFail T.FailMem
386
           | new_failn1 && not (failN1 t) -> T.OpFail T.FailMem
387
           | otherwise ->
388
               let new_slist = iname:sList t
389
                   r = t { sList = new_slist, fDsk = new_dsk
390
                         , peers = new_peers, failN1 = new_failn1
391
                         , rMem = new_rmem, pDsk = new_dp
392
                         , pRem = new_prem, utilLoad = new_load }
393
               in T.OpGood r
394

    
395
-- * Stats functions
396

    
397
-- | Computes the amount of available disk on a given node
398
availDisk :: Node -> Int
399
availDisk t =
400
    let _f = fDsk t
401
        _l = loDsk t
402
    in if _f < _l
403
       then 0
404
       else _f - _l
405

    
406
-- | Computes the amount of available memory on a given node
407
availMem :: Node -> Int
408
availMem t =
409
    let _f = fMem t
410
        _l = rMem t
411
    in if _f < _l
412
       then 0
413
       else _f - _l
414

    
415
-- | Computes the amount of available memory on a given node
416
availCpu :: Node -> Int
417
availCpu t =
418
    let _u = uCpu t
419
        _l = hiCpu t
420
    in if _l >= _u
421
       then _l - _u
422
       else 0
423

    
424
-- * Display functions
425

    
426
showField :: Node -> String -> String
427
showField t field =
428
    case field of
429
      "name" -> name t
430
      "status" -> if offline t then "-"
431
                  else if failN1 t then "*" else " "
432
      "tmem" -> printf "%5.0f" $ tMem t
433
      "nmem" -> printf "%5d" $ nMem t
434
      "xmem" -> printf "%5d" $ xMem t
435
      "fmem" -> printf "%5d" $ fMem t
436
      "imem" -> printf "%5d" imem
437
      "rmem" -> printf "%5d" $ rMem t
438
      "amem" -> printf "%5d" $ fMem t - rMem t
439
      "tdsk" -> printf "%5.0f" $ tDsk t / 1024
440
      "fdsk" -> printf "%5d" $ fDsk t `div` 1024
441
      "tcpu" -> printf "%4.0f" $ tCpu t
442
      "ucpu" -> printf "%4d" $ uCpu t
443
      "plist" -> printf "%3d" $ length (pList t)
444
      "slist" -> printf "%3d" $ length (sList t)
445
      "pfmem" -> printf "%6.4f" $ pMem t
446
      "pfdsk" -> printf "%6.4f" $ pDsk t
447
      "rcpu"  -> printf "%5.2f" $ pCpu t
448
      "cload" -> printf "%5.3f" uC
449
      "mload" -> printf "%5.3f" uM
450
      "dload" -> printf "%5.3f" uD
451
      "nload" -> printf "%5.3f" uN
452
      "ptags" -> intercalate "," . map (\(k, v) -> printf "%s=%d" k v) .
453
                 Map.toList $ pTags t
454
      _ -> printf "<unknown field>"
455
    where
456
      T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
457
                  T.dskWeight = uD, T.netWeight = uN } = utilLoad t
458
      imem = truncate (tMem t) - nMem t - xMem t - fMem t
459

    
460
-- | Returns the header and numeric propery of a field
461
showHeader :: String -> (String, Bool)
462
showHeader field =
463
    case field of
464
      "name" -> ("Name", False)
465
      "status" -> ("F", False)
466
      "tmem" -> ("t_mem", True)
467
      "nmem" -> ("n_mem", True)
468
      "xmem" -> ("x_mem", True)
469
      "fmem" -> ("f_mem", True)
470
      "imem" -> ("i_mem", True)
471
      "rmem" -> ("r_mem", True)
472
      "amem" -> ("a_mem", True)
473
      "tdsk" -> ("t_dsk", True)
474
      "fdsk" -> ("f_dsk", True)
475
      "tcpu" -> ("pcpu", True)
476
      "ucpu" -> ("vcpu", True)
477
      "plist" -> ("pri", True)
478
      "slist" -> ("sec", True)
479
      "pfmem" -> ("p_fmem", True)
480
      "pfdsk" -> ("p_fdsk", True)
481
      "rcpu"  -> ("r_cpu", True)
482
      "cload" -> ("lCpu", True)
483
      "mload" -> ("lMem", True)
484
      "dload" -> ("lDsk", True)
485
      "nload" -> ("lNet", True)
486
      "ptags" -> ("PrimaryTags", False)
487
      _ -> ("<unknown field>", False)
488

    
489
-- | String converter for the node list functionality.
490
list :: [String] -> Node -> [String]
491
list fields t = map (showField t) fields
492

    
493

    
494
defaultFields :: [String]
495
defaultFields =
496
    [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
497
    , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "plist", "slist"
498
    , "pfmem", "pfdsk", "rcpu"
499
    , "cload", "mload", "dload", "nload" ]