Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ f2280553

History | View | Annotate | Download (12.8 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(failN1, name, idx, t_mem, n_mem, f_mem, r_mem,
30
           t_dsk, f_dsk,
31
           t_cpu, u_cpu,
32
           p_mem, p_dsk, p_rem, p_cpu,
33
           m_dsk, m_cpu, lo_dsk, hi_cpu,
34
           plist, slist, offline)
35
    , List
36
    -- * Constructor
37
    , create
38
    -- ** Finalization after data loading
39
    , buildPeers
40
    , setIdx
41
    , setName
42
    , setOffline
43
    , setXmem
44
    , setFmem
45
    , setPri
46
    , setSec
47
    , setMdsk
48
    , setMcpu
49
    , addCpus
50
    -- * Instance (re)location
51
    , removePri
52
    , removeSec
53
    , addPri
54
    , addSec
55
    -- * Stats
56
    , availDisk
57
    -- * Formatting
58
    , list
59
    -- * Misc stuff
60
    , AssocList
61
    , noSecondary
62
    ) where
63

    
64
import Data.List
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 PeerMap
70

    
71
import qualified Ganeti.HTools.Types as T
72

    
73
-- * Type declarations
74

    
75
-- | The node type.
76
data Node = Node { name  :: String -- ^ The node name
77
                 , t_mem :: Double -- ^ Total memory (MiB)
78
                 , n_mem :: Int    -- ^ Node memory (MiB)
79
                 , f_mem :: Int    -- ^ Free memory (MiB)
80
                 , x_mem :: Int    -- ^ Unaccounted memory (MiB)
81
                 , t_dsk :: Double -- ^ Total disk space (MiB)
82
                 , f_dsk :: Int    -- ^ Free disk space (MiB)
83
                 , t_cpu :: Double -- ^ Total CPU count
84
                 , u_cpu :: Int    -- ^ Used VCPU count
85
                 , plist :: [T.Idx]-- ^ List of primary instance indices
86
                 , slist :: [T.Idx]-- ^ List of secondary instance indices
87
                 , idx :: T.Ndx    -- ^ Internal index for book-keeping
88
                 , peers :: PeerMap.PeerMap -- ^ Pnode to instance mapping
89
                 , failN1:: Bool   -- ^ Whether the node has failed n1
90
                 , r_mem :: Int    -- ^ Maximum memory needed for
91
                                   -- failover by primaries of this node
92
                 , p_mem :: Double -- ^ Percent of free memory
93
                 , p_dsk :: Double -- ^ Percent of free disk
94
                 , p_rem :: Double -- ^ Percent of reserved memory
95
                 , p_cpu :: Double -- ^ Ratio of virtual to physical CPUs
96
                 , m_dsk :: Double -- ^ Minimum free disk ratio
97
                 , m_cpu :: Double -- ^ Max ratio of virt-to-phys CPUs
98
                 , lo_dsk :: Int   -- ^ Autocomputed from m_dsk low disk
99
                                   -- threshold
100
                 , hi_cpu :: Int   -- ^ Autocomputed from m_cpu high cpu
101
                                   -- threshold
102
                 , offline :: Bool -- ^ Whether the node should not be used
103
                                   -- for allocations and skipped from
104
                                   -- score computations
105
  } deriving (Show)
106

    
107
instance T.Element Node where
108
    nameOf = name
109
    idxOf = idx
110
    setName = setName
111
    setIdx = setIdx
112

    
113
-- | A simple name for the int, node association list.
114
type AssocList = [(T.Ndx, Node)]
115

    
116
-- | A simple name for a node map.
117
type List = Container.Container Node
118

    
119
-- | Constant node index for a non-moveable instance.
120
noSecondary :: T.Ndx
121
noSecondary = -1
122

    
123
-- | No limit value
124
noLimit :: Double
125
noLimit = -1
126

    
127
-- | No limit int value
128
noLimitInt :: Int
129
noLimitInt = -1
130

    
131
-- * Initialization functions
132

    
133
-- | Create a new node.
134
--
135
-- The index and the peers maps are empty, and will be need to be
136
-- update later via the 'setIdx' and 'buildPeers' functions.
137
create :: String -> Double -> Int -> Int -> Double
138
       -> Int -> Double -> Bool -> Node
139
create name_init mem_t_init mem_n_init mem_f_init
140
       dsk_t_init dsk_f_init cpu_t_init offline_init =
141
    Node
142
    {
143
      name  = name_init,
144
      t_mem = mem_t_init,
145
      n_mem = mem_n_init,
146
      f_mem = mem_f_init,
147
      t_dsk = dsk_t_init,
148
      f_dsk = dsk_f_init,
149
      t_cpu = cpu_t_init,
150
      u_cpu = 0,
151
      plist = [],
152
      slist = [],
153
      failN1 = True,
154
      idx = -1,
155
      peers = PeerMap.empty,
156
      r_mem = 0,
157
      p_mem = (fromIntegral mem_f_init) / mem_t_init,
158
      p_dsk = (fromIntegral dsk_f_init) / dsk_t_init,
159
      p_rem = 0,
160
      p_cpu = 0,
161
      offline = offline_init,
162
      x_mem = 0,
163
      m_dsk = noLimit,
164
      m_cpu = noLimit,
165
      lo_dsk = noLimitInt,
166
      hi_cpu = noLimitInt
167
    }
168

    
169
-- | Changes the index.
170
--
171
-- This is used only during the building of the data structures.
172
setIdx :: Node -> T.Ndx -> Node
173
setIdx t i = t {idx = i}
174

    
175
-- | Changes the name.
176
--
177
-- This is used only during the building of the data structures.
178
setName :: Node -> String -> Node
179
setName t s = t {name = s}
180

    
181
-- | Sets the offline attribute.
182
setOffline :: Node -> Bool -> Node
183
setOffline t val = t { offline = val }
184

    
185
-- | Sets the unnaccounted memory.
186
setXmem :: Node -> Int -> Node
187
setXmem t val = t { x_mem = val }
188

    
189
-- | Sets the max disk usage ratio
190
setMdsk :: Node -> Double -> Node
191
setMdsk t val = t { m_dsk = val,
192
                    lo_dsk = if val == noLimit
193
                             then noLimitInt
194
                             else floor (val * (t_dsk t)) }
195

    
196
-- | Sets the max cpu usage ratio
197
setMcpu :: Node -> Double -> Node
198
setMcpu t val = t { m_cpu = val, hi_cpu = floor (val * (t_cpu t)) }
199

    
200
-- | Computes the maximum reserved memory for peers from a peer map.
201
computeMaxRes :: PeerMap.PeerMap -> PeerMap.Elem
202
computeMaxRes new_peers = PeerMap.maxElem new_peers
203

    
204
-- | Builds the peer map for a given node.
205
buildPeers :: Node -> Instance.List -> Node
206
buildPeers t il =
207
    let mdata = map
208
                (\i_idx -> let inst = Container.find i_idx il
209
                           in (Instance.pnode inst, Instance.mem inst))
210
                (slist t)
211
        pmap = PeerMap.accumArray (+) mdata
212
        new_rmem = computeMaxRes pmap
213
        new_failN1 = computeFailN1 new_rmem (f_mem t) (f_dsk t)
214
        new_prem = (fromIntegral new_rmem) / (t_mem t)
215
    in t {peers=pmap, failN1 = new_failN1, r_mem = new_rmem, p_rem = new_prem}
216

    
217
-- | Assigns an instance to a node as primary without other updates.
218
setPri :: Node -> T.Idx -> Node
219
setPri t idx = t { plist = idx:(plist t) }
220

    
221
-- | Assigns an instance to a node as secondary without other updates.
222
setSec :: Node -> T.Idx -> Node
223
setSec t idx = t { slist = idx:(slist t) }
224

    
225
-- | Add primary cpus to a node
226
addCpus :: Node -> Int -> Node
227
addCpus t count =
228
    let new_count = (u_cpu t) + count
229
    in t { u_cpu = new_count, p_cpu = (fromIntegral new_count) / (t_cpu t) }
230

    
231
-- * Update functions
232

    
233
-- | Sets the free memory.
234
setFmem :: Node -> Int -> Node
235
setFmem t new_mem =
236
    let new_n1 = computeFailN1 (r_mem t) new_mem (f_dsk t)
237
        new_mp = (fromIntegral new_mem) / (t_mem t)
238
    in
239
      t { f_mem = new_mem, failN1 = new_n1, p_mem = new_mp }
240

    
241
-- | Given the rmem, free memory and disk, computes the failn1 status.
242
computeFailN1 :: Int -> Int -> Int -> Bool
243
computeFailN1 new_rmem new_mem new_dsk =
244
    new_mem <= new_rmem || new_dsk <= 0
245

    
246
-- | Given the new free memory and disk, fail if any of them is below zero.
247
failHealth :: Int -> Int -> Bool
248
failHealth new_mem new_dsk = new_mem <= 0 || new_dsk <= 0
249

    
250
-- | Given new limits, check if any of them are overtaken
251
failLimits :: Node -> Double -> Double -> Bool
252
failLimits t new_dsk new_cpu =
253
    let l_dsk = m_dsk t
254
        l_cpu = m_cpu t
255
    in (l_dsk > new_dsk) || (l_cpu >= 0 && l_cpu < new_cpu)
256

    
257
-- | Removes a primary instance.
258
removePri :: Node -> Instance.Instance -> Node
259
removePri t inst =
260
    let iname = Instance.idx inst
261
        new_plist = delete iname (plist t)
262
        new_mem = f_mem t + Instance.mem inst
263
        new_dsk = f_dsk t + Instance.dsk inst
264
        new_mp = (fromIntegral new_mem) / (t_mem t)
265
        new_dp = (fromIntegral new_dsk) / (t_dsk t)
266
        new_failn1 = computeFailN1 (r_mem t) new_mem new_dsk
267
        new_ucpu = (u_cpu t) - (Instance.vcpus inst)
268
        new_rcpu = (fromIntegral new_ucpu) / (t_cpu t)
269
    in t {plist = new_plist, f_mem = new_mem, f_dsk = new_dsk,
270
          failN1 = new_failn1, p_mem = new_mp, p_dsk = new_dp,
271
          u_cpu = new_ucpu, p_cpu = new_rcpu}
272

    
273
-- | Removes a secondary instance.
274
removeSec :: Node -> Instance.Instance -> Node
275
removeSec t inst =
276
    let iname = Instance.idx inst
277
        pnode = Instance.pnode inst
278
        new_slist = delete iname (slist t)
279
        new_dsk = f_dsk t + Instance.dsk inst
280
        old_peers = peers t
281
        old_peem = PeerMap.find pnode old_peers
282
        new_peem =  old_peem - (Instance.mem inst)
283
        new_peers = PeerMap.add pnode new_peem old_peers
284
        old_rmem = r_mem t
285
        new_rmem = if old_peem < old_rmem then
286
                       old_rmem
287
                   else
288
                       computeMaxRes new_peers
289
        new_prem = (fromIntegral new_rmem) / (t_mem t)
290
        new_failn1 = computeFailN1 new_rmem (f_mem t) new_dsk
291
        new_dp = (fromIntegral new_dsk) / (t_dsk t)
292
    in t {slist = new_slist, f_dsk = new_dsk, peers = new_peers,
293
          failN1 = new_failn1, r_mem = new_rmem, p_dsk = new_dp,
294
          p_rem = new_prem}
295

    
296
-- | Adds a primary instance.
297
addPri :: Node -> Instance.Instance -> T.OpResult Node
298
addPri t inst =
299
    let iname = Instance.idx inst
300
        new_mem = f_mem t - Instance.mem inst
301
        new_dsk = f_dsk t - Instance.dsk inst
302
        new_failn1 = computeFailN1 (r_mem t) new_mem new_dsk
303
        new_ucpu = (u_cpu t) + (Instance.vcpus inst)
304
        new_pcpu = (fromIntegral new_ucpu) / (t_cpu t)
305
        new_dp = (fromIntegral new_dsk) / (t_dsk t)
306
    in
307
      if (failHealth new_mem new_dsk) || (new_failn1 && not (failN1 t)) ||
308
         (failLimits t new_dp new_pcpu)
309
      then
310
        T.OpFail T.FailN1
311
      else
312
        let new_plist = iname:(plist t)
313
            new_mp = (fromIntegral new_mem) / (t_mem t)
314
        in
315
        T.OpGood t {plist = new_plist, f_mem = new_mem, f_dsk = new_dsk,
316
                    failN1 = new_failn1, p_mem = new_mp, p_dsk = new_dp,
317
                    u_cpu = new_ucpu, p_cpu = new_pcpu}
318

    
319
-- | Adds a secondary instance.
320
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
321
addSec t inst pdx =
322
    let iname = Instance.idx inst
323
        old_peers = peers t
324
        old_mem = f_mem t
325
        new_dsk = f_dsk t - Instance.dsk inst
326
        new_peem = PeerMap.find pdx old_peers + Instance.mem inst
327
        new_peers = PeerMap.add pdx new_peem old_peers
328
        new_rmem = max (r_mem t) new_peem
329
        new_prem = (fromIntegral new_rmem) / (t_mem t)
330
        new_failn1 = computeFailN1 new_rmem old_mem new_dsk
331
        new_dp = (fromIntegral new_dsk) / (t_dsk t)
332
    in if (failHealth old_mem new_dsk) || (new_failn1 && not (failN1 t)) ||
333
          (failLimits t new_dp noLimit)
334
       then
335
           T.OpFail T.FailN1
336
       else
337
           let new_slist = iname:(slist t)
338
           in
339
             T.OpGood t {slist = new_slist, f_dsk = new_dsk,
340
                         peers = new_peers, failN1 = new_failn1,
341
                         r_mem = new_rmem, p_dsk = new_dp,
342
                         p_rem = new_prem}
343

    
344
-- * Stats functions
345

    
346
-- | Computes the amount of available disk on a given node
347
availDisk :: Node -> Int
348
availDisk t =
349
    let _f = f_dsk t
350
        _l = lo_dsk t
351
    in
352
      if _l == noLimitInt
353
      then _f
354
      else if _f < _l
355
           then 0
356
           else _f - _l
357

    
358
-- * Display functions
359

    
360
-- | String converter for the node list functionality.
361
list :: Int -> Node -> String
362
list mname t =
363
    let pl = length $ plist t
364
        sl = length $ slist t
365
        mp = p_mem t
366
        dp = p_dsk t
367
        cp = p_cpu t
368
        off = offline t
369
        fn = failN1 t
370
        tmem = t_mem t
371
        nmem = n_mem t
372
        xmem = x_mem t
373
        fmem = f_mem t
374
        imem = (truncate tmem) - nmem - xmem - fmem
375
    in
376
      if off
377
         then printf " - %-*s %57s %3d %3d"
378
              mname (name t) "" pl sl
379
         else
380
             printf " %c %-*s %5.0f %5d %5d %5d %5d %5d %5.0f %5d\
381
                    \ %4.0f %4d %3d %3d %6.4f %6.4f %5.2f"
382
                 (if off then '-' else if fn then '*' else ' ')
383
                 mname (name t) tmem nmem imem xmem fmem (r_mem t)
384
                 ((t_dsk t) / 1024) ((f_dsk t) `div` 1024)
385
                 (t_cpu t) (u_cpu t)
386
                 pl sl mp dp cp