Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ f4c0b8c5

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
    ) where
62

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

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

    
72
import qualified Ganeti.HTools.Types as T
73

    
74
-- * Type declarations
75

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

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

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

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

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

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

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

    
135
-- * Helper functions
136

    
137
-- | Add a tag to a tagmap
138
addTag :: TagMap -> String -> TagMap
139
addTag t s = Map.insertWith (+) s 1 t
140

    
141
-- | Add multiple tags
142
addTags :: TagMap -> [String] -> TagMap
143
addTags = foldl' addTag
144

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

    
152
-- | Remove multiple tags
153
delTags :: TagMap -> [String] -> TagMap
154
delTags = foldl' delTag
155

    
156
-- | Check if we can add a list of tags to a tagmap
157
rejectAddTags :: TagMap -> [String] -> Bool
158
rejectAddTags t = any (`Map.member` t)
159

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

    
168
-- * Initialization functions
169

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

    
207
-- | Conversion formula from mDsk/tDsk to loDsk
208
mDskToloDsk :: Double -> Double -> Int
209
mDskToloDsk mval tdsk = floor (mval * tdsk)
210

    
211
-- | Conversion formula from mCpu/tCpu to hiCpu
212
mCpuTohiCpu :: Double -> Double -> Int
213
mCpuTohiCpu mval tcpu = floor (mval * tcpu)
214

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

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

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

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

    
235
-- | Sets the max disk usage ratio
236
setMdsk :: Node -> Double -> Node
237
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
238

    
239
-- | Sets the max cpu usage ratio
240
setMcpu :: Node -> Double -> Node
241
setMcpu t val = t { mCpu = val, hiCpu = mCpuTohiCpu val (tCpu t) }
242

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

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

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

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

    
279
-- * Update functions
280

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

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

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

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

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

    
389
-- * Stats functions
390

    
391
-- | Computes the amount of available disk on a given node
392
availDisk :: Node -> Int
393
availDisk t =
394
    let _f = fDsk t
395
        _l = loDsk t
396
    in if _f < _l
397
       then 0
398
       else _f - _l
399

    
400
-- * Display functions
401

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

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

    
465
-- | String converter for the node list functionality.
466
list :: [String] -> Node -> [String]
467
list fields t = map (showField t) fields
468

    
469

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