Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ bbd8efd2

History | View | Annotate | Download (13.5 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 t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
239

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

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

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

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

    
331
-- * Stats functions
332

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

    
345
-- * Display functions
346

    
347
showField :: Node -> String -> String
348
showField t field =
349
    case field of
350
      "name" -> name t
351
      "status" -> if offline t then "-"
352
                  else if failN1 t then "*" else " "
353
      "tmem" -> printf "%5.0f" $ tMem t
354
      "nmem" -> printf "%5d" $ nMem t
355
      "xmem" -> printf "%5d" $ xMem t
356
      "fmem" -> printf "%5d" $ fMem t
357
      "imem" -> printf "%5d" imem
358
      "rmem" -> printf "%5d" $ rMem t
359
      "tdsk" -> printf "%5.0f" $ tDsk t / 1024
360
      "fdsk" -> printf "%5d" $ fDsk t `div` 1024
361
      "tcpu" -> printf "%4.0f" $ tCpu t
362
      "ucpu" -> printf "%4d" $ uCpu t
363
      "plist" -> printf "%3d" $ length (pList t)
364
      "slist" -> printf "%3d" $ length (sList t)
365
      "pfmem" -> printf "%6.4f" $ pMem t
366
      "pfdsk" -> printf "%6.4f" $ pDsk t
367
      "rcpu"  -> printf "%5.2f" $ pCpu t
368
      "cload" -> printf "%5.3f" uC
369
      "mload" -> printf "%5.3f" uM
370
      "dload" -> printf "%5.3f" uD
371
      "nload" -> printf "%5.3f" uN
372
      _ -> printf "<unknown field>"
373
    where
374
      T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
375
                  T.dskWeight = uD, T.netWeight = uN } = utilLoad t
376
      imem = truncate (tMem t) - nMem t - xMem t - fMem t
377

    
378

    
379
-- | String converter for the node list functionality.
380
list :: Node -> [String]
381
list t = map (showField t)
382
         [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
383
         , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "plist", "slist"
384
         , "pfmem", "pfdsk", "rcpu"
385
         , "cload", "mload", "dload", "nload" ]