Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ 434c15d5

History | View | Annotate | Download (16 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
    , noSecondary
60
    ) where
61

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

    
67
import qualified Ganeti.HTools.Container as Container
68
import qualified Ganeti.HTools.Instance as Instance
69
import qualified Ganeti.HTools.PeerMap as P
70

    
71
import qualified Ganeti.HTools.Types as T
72

    
73
-- * Type declarations
74

    
75
-- | The tag map type
76
type TagMap = Map.Map String Int
77

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

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

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

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

    
126
-- | Constant node index for a non-moveable instance.
127
noSecondary :: T.Ndx
128
noSecondary = -1
129

    
130
-- | No limit value
131
noLimit :: Double
132
noLimit = -1
133

    
134
-- | No limit int value
135
noLimitInt :: Int
136
noLimitInt = -1
137

    
138
-- * Helper functions
139

    
140
-- | Add a tag to a tagmap
141
addTag :: TagMap -> String -> TagMap
142
addTag t s = Map.insertWith (+) s 1 t
143

    
144
-- | Add multiple tags
145
addTags :: TagMap -> [String] -> TagMap
146
addTags = foldl' addTag
147

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

    
155
-- | Remove multiple tags
156
delTags :: TagMap -> [String] -> TagMap
157
delTags = foldl' delTag
158

    
159
-- | Check if we can add a list of tags to a tagmap
160
rejectAddTags :: TagMap -> [String] -> Bool
161
rejectAddTags t = any (flip Map.member t)
162

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

    
171
-- * Initialization functions
172

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

    
210
-- | Changes the index.
211
--
212
-- This is used only during the building of the data structures.
213
setIdx :: Node -> T.Ndx -> Node
214
setIdx t i = t {idx = i}
215

    
216
-- | Changes the name.
217
--
218
-- This is used only during the building of the data structures.
219
setName :: Node -> String -> Node
220
setName t s = t {name = s}
221

    
222
-- | Sets the offline attribute.
223
setOffline :: Node -> Bool -> Node
224
setOffline t val = t { offline = val }
225

    
226
-- | Sets the unnaccounted memory.
227
setXmem :: Node -> Int -> Node
228
setXmem t val = t { xMem = val }
229

    
230
-- | Sets the max disk usage ratio
231
setMdsk :: Node -> Double -> Node
232
setMdsk t val = t { mDsk = val,
233
                    loDsk = if val == noLimit
234
                             then noLimitInt
235
                             else floor (val * tDsk t) }
236

    
237
-- | Sets the max cpu usage ratio
238
setMcpu :: Node -> Double -> Node
239
setMcpu t val = t { mCpu = val, hiCpu = floor (val * tCpu t) }
240

    
241
-- | Computes the maximum reserved memory for peers from a peer map.
242
computeMaxRes :: P.PeerMap -> P.Elem
243
computeMaxRes = P.maxElem
244

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

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

    
269
-- | Assigns an instance to a node as secondary without other updates.
270
setSec :: Node -> Instance.Instance -> Node
271
setSec t inst = t { sList = Instance.idx inst:sList t
272
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
273
                                          T.dskWeight (Instance.util inst) }
274
                  }
275
    where old_load = utilLoad t
276

    
277
-- * Update functions
278

    
279
-- | Sets the free memory.
280
setFmem :: Node -> Int -> Node
281
setFmem t new_mem =
282
    let new_n1 = new_mem <= rMem t
283
        new_mp = fromIntegral new_mem / tMem t
284
    in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
285

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

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

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

    
358
-- | Adds a secondary instance.
359
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
360
addSec t inst pdx =
361
    let iname = Instance.idx inst
362
        old_peers = peers t
363
        old_mem = fMem t
364
        new_dsk = fDsk t - Instance.dsk inst
365
        new_peem = P.find pdx old_peers + Instance.mem inst
366
        new_peers = P.add pdx new_peem old_peers
367
        new_rmem = max (rMem t) new_peem
368
        new_prem = fromIntegral new_rmem / tMem t
369
        new_failn1 = old_mem <= new_rmem
370
        new_dp = fromIntegral new_dsk / tDsk t
371
        old_load = utilLoad t
372
        new_load = old_load { T.dskWeight = T.dskWeight old_load +
373
                                            T.dskWeight (Instance.util inst) }
374
    in if new_dsk <= 0 || mDsk t > new_dp then T.OpFail T.FailDisk
375
       else if new_failn1 && not (failN1 t) then T.OpFail T.FailMem
376
       else let new_slist = iname:sList t
377
                r = t { sList = new_slist, fDsk = new_dsk
378
                      , peers = new_peers, failN1 = new_failn1
379
                      , rMem = new_rmem, pDsk = new_dp
380
                      , pRem = new_prem, utilLoad = new_load }
381
            in T.OpGood r
382

    
383
-- * Stats functions
384

    
385
-- | Computes the amount of available disk on a given node
386
availDisk :: Node -> Int
387
availDisk t =
388
    let _f = fDsk t
389
        _l = loDsk t
390
    in
391
      if _l == noLimitInt
392
      then _f
393
      else if _f < _l
394
           then 0
395
           else _f - _l
396

    
397
-- * Display functions
398

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

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

    
462
-- | String converter for the node list functionality.
463
list :: [String] -> Node -> [String]
464
list fields t = map (showField t) fields
465

    
466

    
467
defaultFields :: [String]
468
defaultFields =
469
    [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
470
    , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "plist", "slist"
471
    , "pfmem", "pfdsk", "rcpu"
472
    , "cload", "mload", "dload", "nload" ]