Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ 836533fa

History | View | Annotate | Download (12.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(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
    -- * Formatting
56
    , list
57
    -- * Misc stuff
58
    , AssocList
59
    , noSecondary
60
    ) where
61

    
62
import Data.List
63
import Text.Printf (printf)
64

    
65
import qualified Ganeti.HTools.Container as Container
66
import qualified Ganeti.HTools.Instance as Instance
67
import qualified Ganeti.HTools.PeerMap as PeerMap
68

    
69
import qualified Ganeti.HTools.Types as T
70

    
71
-- * Type declarations
72

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

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

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

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

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

    
121
-- | No limit value
122
noLimit :: Double
123
noLimit = -1
124

    
125
-- | No limit int value
126
noLimitInt :: Int
127
noLimitInt = -1
128

    
129
-- * Initialization functions
130

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

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

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

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

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

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

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

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

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

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

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

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

    
229
-- * Update functions
230

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

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

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

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

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

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

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

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

    
342
-- * Display functions
343

    
344
-- | String converter for the node list functionality.
345
list :: Int -> Node -> String
346
list mname t =
347
    let pl = length $ plist t
348
        sl = length $ slist t
349
        mp = p_mem t
350
        dp = p_dsk t
351
        cp = p_cpu t
352
        off = offline t
353
        fn = failN1 t
354
        tmem = t_mem t
355
        nmem = n_mem t
356
        xmem = x_mem t
357
        fmem = f_mem t
358
        imem = (truncate tmem) - nmem - xmem - fmem
359
    in
360
      if off
361
         then printf " - %-*s %57s %3d %3d"
362
              mname (name t) "" pl sl
363
         else
364
             printf " %c %-*s %5.0f %5d %5d %5d %5d %5d %5.0f %5d\
365
                    \ %4.0f %4d %3d %3d %6.4f %6.4f %5.2f"
366
                 (if off then '-' else if fn then '*' else ' ')
367
                 mname (name t) tmem nmem imem xmem fmem (r_mem t)
368
                 ((t_dsk t) / 1024) ((f_dsk t) `div` 1024)
369
                 (t_cpu t) (u_cpu t)
370
                 pl sl mp dp cp