Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ ee9724b9

History | View | Annotate | Download (13.2 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
    -- * Formatting
52
    , list
53
    -- * Misc stuff
54
    , AssocList
55
    , noSecondary
56
    ) where
57

    
58
import Data.List
59
import Text.Printf (printf)
60

    
61
import qualified Ganeti.HTools.Container as Container
62
import qualified Ganeti.HTools.Instance as Instance
63
import qualified Ganeti.HTools.PeerMap as PeerMap
64

    
65
import qualified Ganeti.HTools.Types as T
66

    
67
-- * Type declarations
68

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

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

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

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

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

    
119
-- | No limit value
120
noLimit :: Double
121
noLimit = -1
122

    
123
-- | No limit int value
124
noLimitInt :: Int
125
noLimitInt = -1
126

    
127
-- * Initialization functions
128

    
129
-- | Create a new node.
130
--
131
-- The index and the peers maps are empty, and will be need to be
132
-- update later via the 'setIdx' and 'buildPeers' functions.
133
create :: String -> Double -> Int -> Int -> Double
134
       -> Int -> Double -> Bool -> Node
135
create name_init mem_t_init mem_n_init mem_f_init
136
       dsk_t_init dsk_f_init cpu_t_init offline_init =
137
    Node { name  = name_init
138
         , tMem = mem_t_init
139
         , nMem = mem_n_init
140
         , fMem = mem_f_init
141
         , tDsk = dsk_t_init
142
         , fDsk = dsk_f_init
143
         , tCpu = cpu_t_init
144
         , uCpu = 0
145
         , pList = []
146
         , sList = []
147
         , failN1 = True
148
         , idx = -1
149
         , peers = PeerMap.empty
150
         , rMem = 0
151
         , pMem = fromIntegral mem_f_init / mem_t_init
152
         , pDsk = fromIntegral dsk_f_init / dsk_t_init
153
         , pRem = 0
154
         , pCpu = 0
155
         , offline = offline_init
156
         , xMem = 0
157
         , mDsk = noLimit
158
         , mCpu = noLimit
159
         , loDsk = noLimitInt
160
         , hiCpu = noLimitInt
161
         , utilPool = T.baseUtil
162
         , utilLoad = T.zeroUtil
163
         }
164

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

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

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

    
181
-- | Sets the unnaccounted memory.
182
setXmem :: Node -> Int -> Node
183
setXmem t val = t { xMem = val }
184

    
185
-- | Sets the max disk usage ratio
186
setMdsk :: Node -> Double -> Node
187
setMdsk t val = t { mDsk = val,
188
                    loDsk = if val == noLimit
189
                             then noLimitInt
190
                             else floor (val * tDsk t) }
191

    
192
-- | Sets the max cpu usage ratio
193
setMcpu :: Node -> Double -> Node
194
setMcpu t val = t { mCpu = val, hiCpu = floor (val * tCpu t) }
195

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

    
200
-- | Builds the peer map for a given node.
201
buildPeers :: Node -> Instance.List -> Node
202
buildPeers t il =
203
    let mdata = map
204
                (\i_idx -> let inst = Container.find i_idx il
205
                           in (Instance.pNode inst, Instance.mem inst))
206
                (sList t)
207
        pmap = PeerMap.accumArray (+) mdata
208
        new_rmem = computeMaxRes pmap
209
        new_failN1 = fMem t <= new_rmem
210
        new_prem = fromIntegral new_rmem / tMem t
211
    in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
212

    
213
-- | Assigns an instance to a node as primary and update the used VCPU
214
-- count and utilisation data.
215
setPri :: Node -> Instance.Instance -> Node
216
setPri t inst = t { pList = Instance.idx inst:pList t
217
                  , uCpu = new_count
218
                  , pCpu = fromIntegral new_count / tCpu t
219
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
220
                  }
221
    where new_count = uCpu t + Instance.vcpus inst
222

    
223
-- | Assigns an instance to a node as secondary without other updates.
224
setSec :: Node -> Instance.Instance -> Node
225
setSec t inst = t { sList = Instance.idx inst:sList t
226
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
227
                                          T.dskWeight (Instance.util inst) }
228
                  }
229
    where old_load = utilLoad 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 = new_mem <= rMem t
237
        new_mp = fromIntegral new_mem / tMem t
238
    in
239
      t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
240

    
241
-- | Removes a primary instance.
242
removePri :: Node -> Instance.Instance -> Node
243
removePri t inst =
244
    let iname = Instance.idx inst
245
        new_plist = delete iname (pList t)
246
        new_mem = fMem t + Instance.mem inst
247
        new_dsk = fDsk t + Instance.dsk inst
248
        new_mp = fromIntegral new_mem / tMem t
249
        new_dp = fromIntegral new_dsk / tDsk t
250
        new_failn1 = new_mem <= rMem t
251
        new_ucpu = uCpu t - Instance.vcpus inst
252
        new_rcpu = fromIntegral new_ucpu / tCpu t
253
        new_load = utilLoad t `T.subUtil` Instance.util inst
254
    in t {pList = new_plist, fMem = new_mem, fDsk = new_dsk,
255
          failN1 = new_failn1, pMem = new_mp, pDsk = new_dp,
256
          uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load}
257

    
258
-- | Removes a secondary instance.
259
removeSec :: Node -> Instance.Instance -> Node
260
removeSec t inst =
261
    let iname = Instance.idx inst
262
        pnode = Instance.pNode inst
263
        new_slist = delete iname (sList t)
264
        new_dsk = fDsk t + Instance.dsk inst
265
        old_peers = peers t
266
        old_peem = PeerMap.find pnode old_peers
267
        new_peem =  old_peem - Instance.mem inst
268
        new_peers = PeerMap.add pnode new_peem old_peers
269
        old_rmem = rMem t
270
        new_rmem = if old_peem < old_rmem then
271
                       old_rmem
272
                   else
273
                       computeMaxRes new_peers
274
        new_prem = fromIntegral new_rmem / tMem t
275
        new_failn1 = fMem t <= new_rmem
276
        new_dp = fromIntegral new_dsk / tDsk t
277
        old_load = utilLoad t
278
        new_load = old_load { T.dskWeight = T.dskWeight old_load -
279
                                            T.dskWeight (Instance.util inst) }
280
    in t {sList = new_slist, fDsk = new_dsk, peers = new_peers,
281
          failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp,
282
          pRem = new_prem, utilLoad = new_load}
283

    
284
-- | Adds a primary instance.
285
addPri :: Node -> Instance.Instance -> T.OpResult Node
286
addPri t inst =
287
    let iname = Instance.idx inst
288
        new_mem = fMem t - Instance.mem inst
289
        new_dsk = fDsk t - Instance.dsk inst
290
        new_failn1 = new_mem <= rMem t
291
        new_ucpu = uCpu t + Instance.vcpus inst
292
        new_pcpu = fromIntegral new_ucpu / tCpu t
293
        new_dp = fromIntegral new_dsk / tDsk t
294
        l_cpu = mCpu t
295
        new_load = utilLoad t `T.addUtil` Instance.util inst
296
    in if new_mem <= 0 then T.OpFail T.FailMem
297
       else if new_dsk <= 0 || mDsk t > new_dp then T.OpFail T.FailDisk
298
       else if new_failn1 && not (failN1 t) then T.OpFail T.FailMem
299
       else if l_cpu >= 0 && l_cpu < new_pcpu then T.OpFail T.FailCPU
300
       else
301
           let new_plist = iname:pList t
302
               new_mp = fromIntegral new_mem / tMem t
303
               r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk,
304
                       failN1 = new_failn1, pMem = new_mp, pDsk = new_dp,
305
                       uCpu = new_ucpu, pCpu = new_pcpu, utilLoad = new_load }
306
           in T.OpGood r
307

    
308
-- | Adds a secondary instance.
309
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
310
addSec t inst pdx =
311
    let iname = Instance.idx inst
312
        old_peers = peers t
313
        old_mem = fMem t
314
        new_dsk = fDsk t - Instance.dsk inst
315
        new_peem = PeerMap.find pdx old_peers + Instance.mem inst
316
        new_peers = PeerMap.add pdx new_peem old_peers
317
        new_rmem = max (rMem t) new_peem
318
        new_prem = fromIntegral new_rmem / tMem t
319
        new_failn1 = old_mem <= new_rmem
320
        new_dp = fromIntegral new_dsk / tDsk t
321
        old_load = utilLoad t
322
        new_load = old_load { T.dskWeight = T.dskWeight old_load +
323
                                            T.dskWeight (Instance.util inst) }
324
    in if new_dsk <= 0 || mDsk t > new_dp then T.OpFail T.FailDisk
325
       else if new_failn1 && not (failN1 t) then T.OpFail T.FailMem
326
       else let new_slist = iname:sList t
327
                r = t { sList = new_slist, fDsk = new_dsk,
328
                        peers = new_peers, failN1 = new_failn1,
329
                        rMem = new_rmem, pDsk = new_dp,
330
                        pRem = new_prem, utilLoad = new_load }
331
           in T.OpGood r
332

    
333
-- * Stats functions
334

    
335
-- | Computes the amount of available disk on a given node
336
availDisk :: Node -> Int
337
availDisk t =
338
    let _f = fDsk t
339
        _l = loDsk t
340
    in
341
      if _l == noLimitInt
342
      then _f
343
      else if _f < _l
344
           then 0
345
           else _f - _l
346

    
347
-- * Display functions
348

    
349
-- | String converter for the node list functionality.
350
list :: Int -> Node -> String
351
list mname t =
352
    let pl = length $ pList t
353
        sl = length $ sList t
354
        mp = pMem t
355
        dp = pDsk t
356
        cp = pCpu t
357
        off = offline t
358
        fn = failN1 t
359
        tmem = tMem t
360
        nmem = nMem t
361
        xmem = xMem t
362
        fmem = fMem t
363
        imem = truncate tmem - nmem - xmem - fmem
364
        T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
365
                    T.dskWeight = uD, T.netWeight = uN } = utilLoad t
366
        wstr = printf " %5.3f %5.3f %5.3f %5.3f" uC uM uD uN::String
367
    in
368
      if off
369
         then printf " - %-*s %57s %3d %3d"
370
              mname (name t) "" pl sl
371
         else
372
             printf " %c %-*s %5.0f %5d %5d %5d %5d %5d %5.0f %5d\
373
                    \ %4.0f %4d %3d %3d %6.4f %6.4f %5.2f"
374
                 (if off then '-' else if fn then '*' else ' ')
375
                 mname (name t) tmem nmem imem xmem fmem (rMem t)
376
                 (tDsk t / 1024) (fDsk t `div` 1024)
377
                 (tCpu t) (uCpu t)
378
                 pl sl mp dp cp ++ wstr