Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / Node.hs @ f1e64aba

History | View | Annotate | Download (10.9 kB)

1 e4f08c46 Iustin Pop
{-| Module describing a node.
2 e4f08c46 Iustin Pop
3 e4f08c46 Iustin Pop
    All updates are functional (copy-based) and return a new node with
4 e4f08c46 Iustin Pop
    updated value.
5 e4f08c46 Iustin Pop
-}
6 e4f08c46 Iustin Pop
7 e2fa2baf Iustin Pop
{-
8 e2fa2baf Iustin Pop
9 e2fa2baf Iustin Pop
Copyright (C) 2009 Google Inc.
10 e2fa2baf Iustin Pop
11 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
12 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
13 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 e2fa2baf Iustin Pop
(at your option) any later version.
15 e2fa2baf Iustin Pop
16 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
17 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 e2fa2baf Iustin Pop
General Public License for more details.
20 e2fa2baf Iustin Pop
21 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
22 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
23 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 e2fa2baf Iustin Pop
02110-1301, USA.
25 e2fa2baf Iustin Pop
26 e2fa2baf Iustin Pop
-}
27 e2fa2baf Iustin Pop
28 669d7e3d Iustin Pop
module Ganeti.HTools.Node
29 1a82215d Iustin Pop
    ( Node(failN1, name, idx, t_mem, n_mem, f_mem, r_mem,
30 1a82215d Iustin Pop
           t_dsk, f_dsk,
31 1a82215d Iustin Pop
           t_cpu, u_cpu,
32 1a82215d Iustin Pop
           p_mem, p_dsk, p_rem, p_cpu,
33 7847a037 Iustin Pop
           plist, slist, offline)
34 262a08a2 Iustin Pop
    , List
35 e4f08c46 Iustin Pop
    -- * Constructor
36 e4f08c46 Iustin Pop
    , create
37 e4f08c46 Iustin Pop
    -- ** Finalization after data loading
38 e4f08c46 Iustin Pop
    , buildPeers
39 e4f08c46 Iustin Pop
    , setIdx
40 497e30a1 Iustin Pop
    , setName
41 c2c1ef0c Iustin Pop
    , setOffline
42 8c5b0a0d Iustin Pop
    , setXmem
43 53f00b20 Iustin Pop
    , setFmem
44 9188aeef Iustin Pop
    , setPri
45 9188aeef Iustin Pop
    , setSec
46 1a82215d Iustin Pop
    , addCpus
47 e4f08c46 Iustin Pop
    -- * Instance (re)location
48 e4f08c46 Iustin Pop
    , removePri
49 e4f08c46 Iustin Pop
    , removeSec
50 e4f08c46 Iustin Pop
    , addPri
51 e4f08c46 Iustin Pop
    , addSec
52 e4f08c46 Iustin Pop
    -- * Formatting
53 e4f08c46 Iustin Pop
    , list
54 040afc35 Iustin Pop
    -- * Misc stuff
55 040afc35 Iustin Pop
    , AssocList
56 040afc35 Iustin Pop
    , noSecondary
57 e4f08c46 Iustin Pop
    ) where
58 e4f08c46 Iustin Pop
59 e4f08c46 Iustin Pop
import Data.List
60 e4f08c46 Iustin Pop
import Text.Printf (printf)
61 e4f08c46 Iustin Pop
62 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Container as Container
63 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
64 669d7e3d Iustin Pop
import qualified Ganeti.HTools.PeerMap as PeerMap
65 e4f08c46 Iustin Pop
66 262a08a2 Iustin Pop
import qualified Ganeti.HTools.Types as T
67 262a08a2 Iustin Pop
68 9188aeef Iustin Pop
-- * Type declarations
69 9188aeef Iustin Pop
70 9188aeef Iustin Pop
-- | The node type.
71 9188aeef Iustin Pop
data Node = Node { name  :: String -- ^ The node name
72 9188aeef Iustin Pop
                 , t_mem :: Double -- ^ Total memory (MiB)
73 9188aeef Iustin Pop
                 , n_mem :: Int    -- ^ Node memory (MiB)
74 9188aeef Iustin Pop
                 , f_mem :: Int    -- ^ Free memory (MiB)
75 9188aeef Iustin Pop
                 , x_mem :: Int    -- ^ Unaccounted memory (MiB)
76 9188aeef Iustin Pop
                 , t_dsk :: Double -- ^ Total disk space (MiB)
77 9188aeef Iustin Pop
                 , f_dsk :: Int    -- ^ Free disk space (MiB)
78 1a82215d Iustin Pop
                 , t_cpu :: Double -- ^ Total CPU count
79 1a82215d Iustin Pop
                 , u_cpu :: Int    -- ^ Used VCPU count
80 9188aeef Iustin Pop
                 , plist :: [T.Idx]-- ^ List of primary instance indices
81 9188aeef Iustin Pop
                 , slist :: [T.Idx]-- ^ List of secondary instance indices
82 9188aeef Iustin Pop
                 , idx :: T.Ndx    -- ^ Internal index for book-keeping
83 9188aeef Iustin Pop
                 , peers :: PeerMap.PeerMap -- ^ Pnode to instance mapping
84 9188aeef Iustin Pop
                 , failN1:: Bool   -- ^ Whether the node has failed n1
85 9188aeef Iustin Pop
                 , r_mem :: Int    -- ^ Maximum memory needed for
86 80d0d2f1 Iustin Pop
                                   -- failover by primaries of this node
87 9188aeef Iustin Pop
                 , p_mem :: Double -- ^ Percent of free memory
88 9188aeef Iustin Pop
                 , p_dsk :: Double -- ^ Percent of free disk
89 9188aeef Iustin Pop
                 , p_rem :: Double -- ^ Percent of reserved memory
90 1a82215d Iustin Pop
                 , p_cpu :: Double -- ^ Ratio of virtual to physical CPUs
91 9188aeef Iustin Pop
                 , offline :: Bool -- ^ Whether the node should not be used
92 c2c1ef0c Iustin Pop
                                   -- for allocations and skipped from
93 c2c1ef0c Iustin Pop
                                   -- score computations
94 e4f08c46 Iustin Pop
  } deriving (Show)
95 e4f08c46 Iustin Pop
96 262a08a2 Iustin Pop
instance T.Element Node where
97 262a08a2 Iustin Pop
    nameOf = name
98 262a08a2 Iustin Pop
    idxOf = idx
99 262a08a2 Iustin Pop
    setName = setName
100 262a08a2 Iustin Pop
    setIdx = setIdx
101 262a08a2 Iustin Pop
102 9188aeef Iustin Pop
-- | A simple name for the int, node association list.
103 608efcce Iustin Pop
type AssocList = [(T.Ndx, Node)]
104 040afc35 Iustin Pop
105 9188aeef Iustin Pop
-- | A simple name for a node map.
106 262a08a2 Iustin Pop
type List = Container.Container Node
107 262a08a2 Iustin Pop
108 9188aeef Iustin Pop
-- | Constant node index for a non-moveable instance.
109 608efcce Iustin Pop
noSecondary :: T.Ndx
110 040afc35 Iustin Pop
noSecondary = -1
111 040afc35 Iustin Pop
112 9188aeef Iustin Pop
-- * Initialization functions
113 e4f08c46 Iustin Pop
114 9188aeef Iustin Pop
-- | Create a new node.
115 9188aeef Iustin Pop
--
116 9188aeef Iustin Pop
-- The index and the peers maps are empty, and will be need to be
117 9188aeef Iustin Pop
-- update later via the 'setIdx' and 'buildPeers' functions.
118 1a82215d Iustin Pop
create :: String -> Double -> Int -> Int -> Double
119 1a82215d Iustin Pop
       -> Int -> Double -> Bool -> Node
120 2727257a Iustin Pop
create name_init mem_t_init mem_n_init mem_f_init
121 1a82215d Iustin Pop
       dsk_t_init dsk_f_init cpu_t_init offline_init =
122 47a8bade Iustin Pop
    Node
123 47a8bade Iustin Pop
    {
124 2727257a Iustin Pop
      name  = name_init,
125 47a8bade Iustin Pop
      t_mem = mem_t_init,
126 04be800a Iustin Pop
      n_mem = mem_n_init,
127 47a8bade Iustin Pop
      f_mem = mem_f_init,
128 47a8bade Iustin Pop
      t_dsk = dsk_t_init,
129 47a8bade Iustin Pop
      f_dsk = dsk_f_init,
130 1a82215d Iustin Pop
      t_cpu = cpu_t_init,
131 1a82215d Iustin Pop
      u_cpu = 0,
132 47a8bade Iustin Pop
      plist = [],
133 47a8bade Iustin Pop
      slist = [],
134 47a8bade Iustin Pop
      failN1 = True,
135 47a8bade Iustin Pop
      idx = -1,
136 47a8bade Iustin Pop
      peers = PeerMap.empty,
137 47a8bade Iustin Pop
      r_mem = 0,
138 47a8bade Iustin Pop
      p_mem = (fromIntegral mem_f_init) / mem_t_init,
139 47a8bade Iustin Pop
      p_dsk = (fromIntegral dsk_f_init) / dsk_t_init,
140 47a8bade Iustin Pop
      p_rem = 0,
141 1a82215d Iustin Pop
      p_cpu = 0,
142 00b15752 Iustin Pop
      offline = offline_init,
143 8c5b0a0d Iustin Pop
      x_mem = 0
144 47a8bade Iustin Pop
    }
145 e4f08c46 Iustin Pop
146 e4f08c46 Iustin Pop
-- | Changes the index.
147 9188aeef Iustin Pop
--
148 e4f08c46 Iustin Pop
-- This is used only during the building of the data structures.
149 608efcce Iustin Pop
setIdx :: Node -> T.Ndx -> Node
150 e4f08c46 Iustin Pop
setIdx t i = t {idx = i}
151 e4f08c46 Iustin Pop
152 9188aeef Iustin Pop
-- | Changes the name.
153 9188aeef Iustin Pop
--
154 497e30a1 Iustin Pop
-- This is used only during the building of the data structures.
155 9188aeef Iustin Pop
setName :: Node -> String -> Node
156 497e30a1 Iustin Pop
setName t s = t {name = s}
157 497e30a1 Iustin Pop
158 9188aeef Iustin Pop
-- | Sets the offline attribute.
159 c2c1ef0c Iustin Pop
setOffline :: Node -> Bool -> Node
160 c2c1ef0c Iustin Pop
setOffline t val = t { offline = val }
161 c2c1ef0c Iustin Pop
162 9188aeef Iustin Pop
-- | Sets the unnaccounted memory.
163 8c5b0a0d Iustin Pop
setXmem :: Node -> Int -> Node
164 8c5b0a0d Iustin Pop
setXmem t val = t { x_mem = val }
165 8c5b0a0d Iustin Pop
166 e4f08c46 Iustin Pop
-- | Computes the maximum reserved memory for peers from a peer map.
167 e4f08c46 Iustin Pop
computeMaxRes :: PeerMap.PeerMap -> PeerMap.Elem
168 e4f08c46 Iustin Pop
computeMaxRes new_peers = PeerMap.maxElem new_peers
169 e4f08c46 Iustin Pop
170 e4f08c46 Iustin Pop
-- | Builds the peer map for a given node.
171 9cf4267a Iustin Pop
buildPeers :: Node -> Instance.List -> Node
172 9cf4267a Iustin Pop
buildPeers t il =
173 e4f08c46 Iustin Pop
    let mdata = map
174 e4f08c46 Iustin Pop
                (\i_idx -> let inst = Container.find i_idx il
175 e4f08c46 Iustin Pop
                           in (Instance.pnode inst, Instance.mem inst))
176 e4f08c46 Iustin Pop
                (slist t)
177 17c59f4b Iustin Pop
        pmap = PeerMap.accumArray (+) mdata
178 e4f08c46 Iustin Pop
        new_rmem = computeMaxRes pmap
179 962367fe Iustin Pop
        new_failN1 = computeFailN1 new_rmem (f_mem t) (f_dsk t)
180 dfc749e6 Iustin Pop
        new_prem = (fromIntegral new_rmem) / (t_mem t)
181 c622fa7c Iustin Pop
    in t {peers=pmap, failN1 = new_failN1, r_mem = new_rmem, p_rem = new_prem}
182 e4f08c46 Iustin Pop
183 9188aeef Iustin Pop
-- | Assigns an instance to a node as primary without other updates.
184 9188aeef Iustin Pop
setPri :: Node -> T.Idx -> Node
185 9188aeef Iustin Pop
setPri t idx = t { plist = idx:(plist t) }
186 9188aeef Iustin Pop
187 9188aeef Iustin Pop
-- | Assigns an instance to a node as secondary without other updates.
188 9188aeef Iustin Pop
setSec :: Node -> T.Idx -> Node
189 9188aeef Iustin Pop
setSec t idx = t { slist = idx:(slist t) }
190 9188aeef Iustin Pop
191 1a82215d Iustin Pop
-- | Add primary cpus to a node
192 1a82215d Iustin Pop
addCpus :: Node -> Int -> Node
193 1a82215d Iustin Pop
addCpus t count =
194 1a82215d Iustin Pop
    let new_count = (u_cpu t) + count
195 1a82215d Iustin Pop
    in t { u_cpu = new_count, p_cpu = (fromIntegral new_count) / (t_cpu t) }
196 1a82215d Iustin Pop
197 9188aeef Iustin Pop
-- * Update functions
198 9188aeef Iustin Pop
199 9188aeef Iustin Pop
-- | Sets the free memory.
200 9188aeef Iustin Pop
setFmem :: Node -> Int -> Node
201 9188aeef Iustin Pop
setFmem t new_mem =
202 9188aeef Iustin Pop
    let new_n1 = computeFailN1 (r_mem t) new_mem (f_dsk t)
203 9188aeef Iustin Pop
        new_mp = (fromIntegral new_mem) / (t_mem t)
204 9188aeef Iustin Pop
    in
205 9188aeef Iustin Pop
      t { f_mem = new_mem, failN1 = new_n1, p_mem = new_mp }
206 9188aeef Iustin Pop
207 9188aeef Iustin Pop
-- | Given the rmem, free memory and disk, computes the failn1 status.
208 9188aeef Iustin Pop
computeFailN1 :: Int -> Int -> Int -> Bool
209 9188aeef Iustin Pop
computeFailN1 new_rmem new_mem new_dsk =
210 9188aeef Iustin Pop
    new_mem <= new_rmem || new_dsk <= 0
211 9188aeef Iustin Pop
212 9188aeef Iustin Pop
-- | Given the new free memory and disk, fail if any of them is below zero.
213 9188aeef Iustin Pop
failHealth :: Int -> Int -> Bool
214 9188aeef Iustin Pop
failHealth new_mem new_dsk = new_mem <= 0 || new_dsk <= 0
215 9188aeef Iustin Pop
216 e4f08c46 Iustin Pop
-- | Removes a primary instance.
217 e4f08c46 Iustin Pop
removePri :: Node -> Instance.Instance -> Node
218 e4f08c46 Iustin Pop
removePri t inst =
219 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
220 e4f08c46 Iustin Pop
        new_plist = delete iname (plist t)
221 e4f08c46 Iustin Pop
        new_mem = f_mem t + Instance.mem inst
222 962367fe Iustin Pop
        new_dsk = f_dsk t + Instance.dsk inst
223 38f63ae6 Iustin Pop
        new_mp = (fromIntegral new_mem) / (t_mem t)
224 38f63ae6 Iustin Pop
        new_dp = (fromIntegral new_dsk) / (t_dsk t)
225 c622fa7c Iustin Pop
        new_failn1 = computeFailN1 (r_mem t) new_mem new_dsk
226 f1e64aba Iustin Pop
        new_ucpu = (u_cpu t) - (Instance.vcpus inst)
227 f1e64aba Iustin Pop
        new_rcpu = (fromIntegral new_ucpu) / (t_cpu t)
228 962367fe Iustin Pop
    in t {plist = new_plist, f_mem = new_mem, f_dsk = new_dsk,
229 f1e64aba Iustin Pop
          failN1 = new_failn1, p_mem = new_mp, p_dsk = new_dp,
230 f1e64aba Iustin Pop
          u_cpu = new_ucpu, p_cpu = new_rcpu}
231 e4f08c46 Iustin Pop
232 e4f08c46 Iustin Pop
-- | Removes a secondary instance.
233 e4f08c46 Iustin Pop
removeSec :: Node -> Instance.Instance -> Node
234 e4f08c46 Iustin Pop
removeSec t inst =
235 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
236 e4f08c46 Iustin Pop
        pnode = Instance.pnode inst
237 e4f08c46 Iustin Pop
        new_slist = delete iname (slist t)
238 962367fe Iustin Pop
        new_dsk = f_dsk t + Instance.dsk inst
239 e4f08c46 Iustin Pop
        old_peers = peers t
240 e4f08c46 Iustin Pop
        old_peem = PeerMap.find pnode old_peers
241 e4f08c46 Iustin Pop
        new_peem =  old_peem - (Instance.mem inst)
242 e4f08c46 Iustin Pop
        new_peers = PeerMap.add pnode new_peem old_peers
243 c622fa7c Iustin Pop
        old_rmem = r_mem t
244 e4f08c46 Iustin Pop
        new_rmem = if old_peem < old_rmem then
245 e4f08c46 Iustin Pop
                       old_rmem
246 e4f08c46 Iustin Pop
                   else
247 e4f08c46 Iustin Pop
                       computeMaxRes new_peers
248 dfc749e6 Iustin Pop
        new_prem = (fromIntegral new_rmem) / (t_mem t)
249 962367fe Iustin Pop
        new_failn1 = computeFailN1 new_rmem (f_mem t) new_dsk
250 38f63ae6 Iustin Pop
        new_dp = (fromIntegral new_dsk) / (t_dsk t)
251 962367fe Iustin Pop
    in t {slist = new_slist, f_dsk = new_dsk, peers = new_peers,
252 c622fa7c Iustin Pop
          failN1 = new_failn1, r_mem = new_rmem, p_dsk = new_dp,
253 dfc749e6 Iustin Pop
          p_rem = new_prem}
254 e4f08c46 Iustin Pop
255 e4f08c46 Iustin Pop
-- | Adds a primary instance.
256 e4f08c46 Iustin Pop
addPri :: Node -> Instance.Instance -> Maybe Node
257 e4f08c46 Iustin Pop
addPri t inst =
258 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
259 e4f08c46 Iustin Pop
        new_mem = f_mem t - Instance.mem inst
260 962367fe Iustin Pop
        new_dsk = f_dsk t - Instance.dsk inst
261 f1e64aba Iustin Pop
        new_failn1 = computeFailN1 (r_mem t) new_mem new_dsk
262 f1e64aba Iustin Pop
        new_ucpu = (u_cpu t) + (Instance.vcpus inst)
263 f1e64aba Iustin Pop
        new_pcpu = (fromIntegral new_ucpu) / (t_cpu t)
264 f1e64aba Iustin Pop
    in
265 d10b27ef Iustin Pop
      if (failHealth new_mem new_dsk) || (new_failn1 && not (failN1 t)) then
266 e4f08c46 Iustin Pop
        Nothing
267 e4f08c46 Iustin Pop
      else
268 0335fe4a Iustin Pop
        let new_plist = iname:(plist t)
269 38f63ae6 Iustin Pop
            new_mp = (fromIntegral new_mem) / (t_mem t)
270 38f63ae6 Iustin Pop
            new_dp = (fromIntegral new_dsk) / (t_dsk t)
271 0335fe4a Iustin Pop
        in
272 962367fe Iustin Pop
        Just t {plist = new_plist, f_mem = new_mem, f_dsk = new_dsk,
273 f1e64aba Iustin Pop
                failN1 = new_failn1, p_mem = new_mp, p_dsk = new_dp,
274 f1e64aba Iustin Pop
                u_cpu = new_ucpu, p_cpu = new_pcpu}
275 e4f08c46 Iustin Pop
276 e4f08c46 Iustin Pop
-- | Adds a secondary instance.
277 608efcce Iustin Pop
addSec :: Node -> Instance.Instance -> T.Ndx -> Maybe Node
278 e4f08c46 Iustin Pop
addSec t inst pdx =
279 e4f08c46 Iustin Pop
    let iname = Instance.idx inst
280 e4f08c46 Iustin Pop
        old_peers = peers t
281 d10b27ef Iustin Pop
        old_mem = f_mem t
282 962367fe Iustin Pop
        new_dsk = f_dsk t - Instance.dsk inst
283 e4f08c46 Iustin Pop
        new_peem = PeerMap.find pdx old_peers + Instance.mem inst
284 e4f08c46 Iustin Pop
        new_peers = PeerMap.add pdx new_peem old_peers
285 c622fa7c Iustin Pop
        new_rmem = max (r_mem t) new_peem
286 dfc749e6 Iustin Pop
        new_prem = (fromIntegral new_rmem) / (t_mem t)
287 d10b27ef Iustin Pop
        new_failn1 = computeFailN1 new_rmem old_mem new_dsk in
288 d10b27ef Iustin Pop
    if (failHealth old_mem new_dsk) || (new_failn1 && not (failN1 t)) then
289 e4f08c46 Iustin Pop
        Nothing
290 e4f08c46 Iustin Pop
    else
291 0335fe4a Iustin Pop
        let new_slist = iname:(slist t)
292 38f63ae6 Iustin Pop
            new_dp = (fromIntegral new_dsk) / (t_dsk t)
293 0335fe4a Iustin Pop
        in
294 962367fe Iustin Pop
        Just t {slist = new_slist, f_dsk = new_dsk,
295 e4f08c46 Iustin Pop
                peers = new_peers, failN1 = new_failn1,
296 c622fa7c Iustin Pop
                r_mem = new_rmem, p_dsk = new_dp,
297 dfc749e6 Iustin Pop
                p_rem = new_prem}
298 e4f08c46 Iustin Pop
299 9188aeef Iustin Pop
-- * Display functions
300 01f6a5d2 Iustin Pop
301 e4f08c46 Iustin Pop
-- | String converter for the node list functionality.
302 dbd6700b Iustin Pop
list :: Int -> Node -> String
303 dbd6700b Iustin Pop
list mname t =
304 e4f08c46 Iustin Pop
    let pl = plist t
305 e4f08c46 Iustin Pop
        sl = slist t
306 0335fe4a Iustin Pop
        mp = p_mem t
307 0335fe4a Iustin Pop
        dp = p_dsk t
308 1a82215d Iustin Pop
        cp = p_cpu t
309 352806f7 Iustin Pop
        off = offline t
310 2cf878a5 Iustin Pop
        fn = failN1 t
311 a1c6212e Iustin Pop
        tmem = t_mem t
312 a1c6212e Iustin Pop
        nmem = n_mem t
313 a1c6212e Iustin Pop
        xmem = x_mem t
314 a1c6212e Iustin Pop
        fmem = f_mem t
315 a1c6212e Iustin Pop
        imem = (truncate tmem) - nmem - xmem - fmem
316 e4f08c46 Iustin Pop
    in
317 1a82215d Iustin Pop
      printf " %c %-*s %5.0f %5d %5d %5d %5d %5d %5.0f %5d %3d %3d\
318 1a82215d Iustin Pop
             \ %.5f %.5f %.5f"
319 352806f7 Iustin Pop
                 (if off then '-' else if fn then '*' else ' ')
320 dbd6700b Iustin Pop
                 mname (name t) tmem nmem imem xmem fmem (r_mem t)
321 ced859f3 Iustin Pop
                 ((t_dsk t) / 1024) ((f_dsk t) `div` 1024)
322 e4f08c46 Iustin Pop
                 (length pl) (length sl)
323 1a82215d Iustin Pop
                 mp dp cp