Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ 86ecce4a

History | View | Annotate | Download (16.4 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
    -- * Instance (re)location
45
    , removePri
46
    , removeSec
47
    , addPri
48
    , addSec
49
    -- * Stats
50
    , availDisk
51
    , conflictingPrimaries
52
    -- * Formatting
53
    , defaultFields
54
    , showHeader
55
    , showField
56
    , list
57
    -- * Misc stuff
58
    , AssocList
59
    , AllocElement
60
    , noSecondary
61
    , noLimitInt
62
    ) where
63

    
64
import Data.List
65
import qualified Data.Map as Map
66
import qualified Data.Foldable as Foldable
67
import Text.Printf (printf)
68

    
69
import qualified Ganeti.HTools.Container as Container
70
import qualified Ganeti.HTools.Instance as Instance
71
import qualified Ganeti.HTools.PeerMap as P
72

    
73
import qualified Ganeti.HTools.Types as T
74

    
75
-- * Type declarations
76

    
77
-- | The tag map type
78
type TagMap = Map.Map String Int
79

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

    
116
instance T.Element Node where
117
    nameOf = name
118
    idxOf = idx
119
    setName = setName
120
    setIdx = setIdx
121

    
122
-- | A simple name for the int, node association list.
123
type AssocList = [(T.Ndx, Node)]
124

    
125
-- | A simple name for a node map.
126
type List = Container.Container Node
127

    
128
-- | A simple name for an allocation element (here just for logistic
129
-- reasons)
130
type AllocElement = (List, Instance.Instance, [Node])
131

    
132
-- | Constant node index for a non-moveable instance.
133
noSecondary :: T.Ndx
134
noSecondary = -1
135

    
136
-- | No limit value
137
noLimit :: Double
138
noLimit = -1
139

    
140
-- | No limit int value
141
noLimitInt :: Int
142
noLimitInt = -1
143

    
144
-- * Helper functions
145

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

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

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

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

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

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

    
177
-- * Initialization functions
178

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

    
216
-- | Changes the index.
217
--
218
-- This is used only during the building of the data structures.
219
setIdx :: Node -> T.Ndx -> Node
220
setIdx t i = t {idx = i}
221

    
222
-- | Changes the name.
223
--
224
-- This is used only during the building of the data structures.
225
setName :: Node -> String -> Node
226
setName t s = t {name = s}
227

    
228
-- | Sets the offline attribute.
229
setOffline :: Node -> Bool -> Node
230
setOffline t val = t { offline = val }
231

    
232
-- | Sets the unnaccounted memory.
233
setXmem :: Node -> Int -> Node
234
setXmem t val = t { xMem = val }
235

    
236
-- | Sets the max disk usage ratio
237
setMdsk :: Node -> Double -> Node
238
setMdsk t val = t { mDsk = val,
239
                    loDsk = if val == noLimit
240
                             then noLimitInt
241
                             else floor (val * tDsk t) }
242

    
243
-- | Sets the max cpu usage ratio
244
setMcpu :: Node -> Double -> Node
245
setMcpu t val = t { mCpu = val, hiCpu = floor (val * tCpu t) }
246

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

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

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

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

    
283
-- * Update functions
284

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

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

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

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

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

    
393
-- * Stats functions
394

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

    
407
-- * Display functions
408

    
409
showField :: Node -> String -> String
410
showField t field =
411
    case field of
412
      "name" -> name t
413
      "status" -> if offline t then "-"
414
                  else if failN1 t then "*" else " "
415
      "tmem" -> printf "%5.0f" $ tMem t
416
      "nmem" -> printf "%5d" $ nMem t
417
      "xmem" -> printf "%5d" $ xMem t
418
      "fmem" -> printf "%5d" $ fMem t
419
      "imem" -> printf "%5d" imem
420
      "rmem" -> printf "%5d" $ rMem t
421
      "amem" -> printf "%5d" $ fMem t - rMem t
422
      "tdsk" -> printf "%5.0f" $ tDsk t / 1024
423
      "fdsk" -> printf "%5d" $ fDsk t `div` 1024
424
      "tcpu" -> printf "%4.0f" $ tCpu t
425
      "ucpu" -> printf "%4d" $ uCpu t
426
      "plist" -> printf "%3d" $ length (pList t)
427
      "slist" -> printf "%3d" $ length (sList t)
428
      "pfmem" -> printf "%6.4f" $ pMem t
429
      "pfdsk" -> printf "%6.4f" $ pDsk t
430
      "rcpu"  -> printf "%5.2f" $ pCpu t
431
      "cload" -> printf "%5.3f" uC
432
      "mload" -> printf "%5.3f" uM
433
      "dload" -> printf "%5.3f" uD
434
      "nload" -> printf "%5.3f" uN
435
      "ptags" -> intercalate "," . map (\(k, v) -> printf "%s=%d" k v) .
436
                 Map.toList $ pTags t
437
      _ -> printf "<unknown field>"
438
    where
439
      T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
440
                  T.dskWeight = uD, T.netWeight = uN } = utilLoad t
441
      imem = truncate (tMem t) - nMem t - xMem t - fMem t
442

    
443
-- | Returns the header and numeric propery of a field
444
showHeader :: String -> (String, Bool)
445
showHeader field =
446
    case field of
447
      "name" -> ("Name", False)
448
      "status" -> ("F", False)
449
      "tmem" -> ("t_mem", True)
450
      "nmem" -> ("n_mem", True)
451
      "xmem" -> ("x_mem", True)
452
      "fmem" -> ("f_mem", True)
453
      "imem" -> ("i_mem", True)
454
      "rmem" -> ("r_mem", True)
455
      "amem" -> ("a_mem", True)
456
      "tdsk" -> ("t_dsk", True)
457
      "fdsk" -> ("f_dsk", True)
458
      "tcpu" -> ("pcpu", True)
459
      "ucpu" -> ("vcpu", True)
460
      "plist" -> ("pri", True)
461
      "slist" -> ("sec", True)
462
      "pfmem" -> ("p_fmem", True)
463
      "pfdsk" -> ("p_fdsk", True)
464
      "rcpu"  -> ("r_cpu", True)
465
      "cload" -> ("lCpu", True)
466
      "mload" -> ("lMem", True)
467
      "dload" -> ("lDsk", True)
468
      "nload" -> ("lNet", True)
469
      "ptags" -> ("PrimaryTags", False)
470
      _ -> ("<unknown field>", False)
471

    
472
-- | String converter for the node list functionality.
473
list :: [String] -> Node -> [String]
474
list fields t = map (showField t) fields
475

    
476

    
477
defaultFields :: [String]
478
defaultFields =
479
    [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
480
    , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "plist", "slist"
481
    , "pfmem", "pfdsk", "rcpu"
482
    , "cload", "mload", "dload", "nload" ]