c9df51bd16a359ef0c3d8a9e0ed10e35ca7c14e5
[ganeti-local] / Ganeti / HTools / Node.hs
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,
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                  , offline :: Bool -- ^ Whether the node should not be used
97                                    -- for allocations and skipped from
98                                    -- score computations
99   } deriving (Show)
100
101 instance T.Element Node where
102     nameOf = name
103     idxOf = idx
104     setName = setName
105     setIdx = setIdx
106
107 -- | A simple name for the int, node association list.
108 type AssocList = [(T.Ndx, Node)]
109
110 -- | A simple name for a node map.
111 type List = Container.Container Node
112
113 -- | Constant node index for a non-moveable instance.
114 noSecondary :: T.Ndx
115 noSecondary = -1
116
117 -- | No limit value
118 noLimit :: Double
119 noLimit = -1
120
121 -- * Initialization functions
122
123 -- | Create a new node.
124 --
125 -- The index and the peers maps are empty, and will be need to be
126 -- update later via the 'setIdx' and 'buildPeers' functions.
127 create :: String -> Double -> Int -> Int -> Double
128        -> Int -> Double -> Bool -> Node
129 create name_init mem_t_init mem_n_init mem_f_init
130        dsk_t_init dsk_f_init cpu_t_init offline_init =
131     Node
132     {
133       name  = name_init,
134       t_mem = mem_t_init,
135       n_mem = mem_n_init,
136       f_mem = mem_f_init,
137       t_dsk = dsk_t_init,
138       f_dsk = dsk_f_init,
139       t_cpu = cpu_t_init,
140       u_cpu = 0,
141       plist = [],
142       slist = [],
143       failN1 = True,
144       idx = -1,
145       peers = PeerMap.empty,
146       r_mem = 0,
147       p_mem = (fromIntegral mem_f_init) / mem_t_init,
148       p_dsk = (fromIntegral dsk_f_init) / dsk_t_init,
149       p_rem = 0,
150       p_cpu = 0,
151       offline = offline_init,
152       x_mem = 0,
153       m_dsk = noLimit,
154       m_cpu = noLimit
155     }
156
157 -- | Changes the index.
158 --
159 -- This is used only during the building of the data structures.
160 setIdx :: Node -> T.Ndx -> Node
161 setIdx t i = t {idx = i}
162
163 -- | Changes the name.
164 --
165 -- This is used only during the building of the data structures.
166 setName :: Node -> String -> Node
167 setName t s = t {name = s}
168
169 -- | Sets the offline attribute.
170 setOffline :: Node -> Bool -> Node
171 setOffline t val = t { offline = val }
172
173 -- | Sets the unnaccounted memory.
174 setXmem :: Node -> Int -> Node
175 setXmem t val = t { x_mem = val }
176
177 -- | Sets the max disk usage ratio
178 setMdsk :: Node -> Double -> Node
179 setMdsk t val = t { m_dsk = val }
180
181 -- | Sets the max cpu usage ratio
182 setMcpu :: Node -> Double -> Node
183 setMcpu t val = t { m_cpu = val }
184
185 -- | Computes the maximum reserved memory for peers from a peer map.
186 computeMaxRes :: PeerMap.PeerMap -> PeerMap.Elem
187 computeMaxRes new_peers = PeerMap.maxElem new_peers
188
189 -- | Builds the peer map for a given node.
190 buildPeers :: Node -> Instance.List -> Node
191 buildPeers t il =
192     let mdata = map
193                 (\i_idx -> let inst = Container.find i_idx il
194                            in (Instance.pnode inst, Instance.mem inst))
195                 (slist t)
196         pmap = PeerMap.accumArray (+) mdata
197         new_rmem = computeMaxRes pmap
198         new_failN1 = computeFailN1 new_rmem (f_mem t) (f_dsk t)
199         new_prem = (fromIntegral new_rmem) / (t_mem t)
200     in t {peers=pmap, failN1 = new_failN1, r_mem = new_rmem, p_rem = new_prem}
201
202 -- | Assigns an instance to a node as primary without other updates.
203 setPri :: Node -> T.Idx -> Node
204 setPri t idx = t { plist = idx:(plist t) }
205
206 -- | Assigns an instance to a node as secondary without other updates.
207 setSec :: Node -> T.Idx -> Node
208 setSec t idx = t { slist = idx:(slist t) }
209
210 -- | Add primary cpus to a node
211 addCpus :: Node -> Int -> Node
212 addCpus t count =
213     let new_count = (u_cpu t) + count
214     in t { u_cpu = new_count, p_cpu = (fromIntegral new_count) / (t_cpu t) }
215
216 -- * Update functions
217
218 -- | Sets the free memory.
219 setFmem :: Node -> Int -> Node
220 setFmem t new_mem =
221     let new_n1 = computeFailN1 (r_mem t) new_mem (f_dsk t)
222         new_mp = (fromIntegral new_mem) / (t_mem t)
223     in
224       t { f_mem = new_mem, failN1 = new_n1, p_mem = new_mp }
225
226 -- | Given the rmem, free memory and disk, computes the failn1 status.
227 computeFailN1 :: Int -> Int -> Int -> Bool
228 computeFailN1 new_rmem new_mem new_dsk =
229     new_mem <= new_rmem || new_dsk <= 0
230
231 -- | Given the new free memory and disk, fail if any of them is below zero.
232 failHealth :: Int -> Int -> Bool
233 failHealth new_mem new_dsk = new_mem <= 0 || new_dsk <= 0
234
235 -- | Given new limits, check if any of them are overtaken
236 failLimits :: Node -> Double -> Double -> Bool
237 failLimits t new_dsk new_cpu =
238     let l_dsk = m_dsk t
239         l_cpu = m_cpu t
240     in (l_dsk > new_dsk) || (l_cpu >= 0 && l_cpu < new_cpu)
241
242 -- | Removes a primary instance.
243 removePri :: Node -> Instance.Instance -> Node
244 removePri t inst =
245     let iname = Instance.idx inst
246         new_plist = delete iname (plist t)
247         new_mem = f_mem t + Instance.mem inst
248         new_dsk = f_dsk t + Instance.dsk inst
249         new_mp = (fromIntegral new_mem) / (t_mem t)
250         new_dp = (fromIntegral new_dsk) / (t_dsk t)
251         new_failn1 = computeFailN1 (r_mem t) new_mem new_dsk
252         new_ucpu = (u_cpu t) - (Instance.vcpus inst)
253         new_rcpu = (fromIntegral new_ucpu) / (t_cpu t)
254     in t {plist = new_plist, f_mem = new_mem, f_dsk = new_dsk,
255           failN1 = new_failn1, p_mem = new_mp, p_dsk = new_dp,
256           u_cpu = new_ucpu, p_cpu = new_rcpu}
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 = f_dsk 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 = r_mem 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) / (t_mem t)
275         new_failn1 = computeFailN1 new_rmem (f_mem t) new_dsk
276         new_dp = (fromIntegral new_dsk) / (t_dsk t)
277     in t {slist = new_slist, f_dsk = new_dsk, peers = new_peers,
278           failN1 = new_failn1, r_mem = new_rmem, p_dsk = new_dp,
279           p_rem = new_prem}
280
281 -- | Adds a primary instance.
282 addPri :: Node -> Instance.Instance -> Maybe Node
283 addPri t inst =
284     let iname = Instance.idx inst
285         new_mem = f_mem t - Instance.mem inst
286         new_dsk = f_dsk t - Instance.dsk inst
287         new_failn1 = computeFailN1 (r_mem t) new_mem new_dsk
288         new_ucpu = (u_cpu t) + (Instance.vcpus inst)
289         new_pcpu = (fromIntegral new_ucpu) / (t_cpu t)
290         new_dp = (fromIntegral new_dsk) / (t_dsk t)
291     in
292       if (failHealth new_mem new_dsk) || (new_failn1 && not (failN1 t)) ||
293          (failLimits t new_dp new_pcpu)
294       then
295         Nothing
296       else
297         let new_plist = iname:(plist t)
298             new_mp = (fromIntegral new_mem) / (t_mem t)
299         in
300         Just t {plist = new_plist, f_mem = new_mem, f_dsk = new_dsk,
301                 failN1 = new_failn1, p_mem = new_mp, p_dsk = new_dp,
302                 u_cpu = new_ucpu, p_cpu = new_pcpu}
303
304 -- | Adds a secondary instance.
305 addSec :: Node -> Instance.Instance -> T.Ndx -> Maybe Node
306 addSec t inst pdx =
307     let iname = Instance.idx inst
308         old_peers = peers t
309         old_mem = f_mem t
310         new_dsk = f_dsk t - Instance.dsk inst
311         new_peem = PeerMap.find pdx old_peers + Instance.mem inst
312         new_peers = PeerMap.add pdx new_peem old_peers
313         new_rmem = max (r_mem t) new_peem
314         new_prem = (fromIntegral new_rmem) / (t_mem t)
315         new_failn1 = computeFailN1 new_rmem old_mem new_dsk
316         new_dp = (fromIntegral new_dsk) / (t_dsk t)
317     in if (failHealth old_mem new_dsk) || (new_failn1 && not (failN1 t)) ||
318           (failLimits t new_dp noLimit)
319        then
320            Nothing
321        else
322            let new_slist = iname:(slist t)
323            in
324              Just t {slist = new_slist, f_dsk = new_dsk,
325                      peers = new_peers, failN1 = new_failn1,
326                      r_mem = new_rmem, p_dsk = new_dp,
327                      p_rem = new_prem}
328
329 -- * Display functions
330
331 -- | String converter for the node list functionality.
332 list :: Int -> Node -> String
333 list mname t =
334     let pl = length $ plist t
335         sl = length $ slist t
336         mp = p_mem t
337         dp = p_dsk t
338         cp = p_cpu t
339         off = offline t
340         fn = failN1 t
341         tmem = t_mem t
342         nmem = n_mem t
343         xmem = x_mem t
344         fmem = f_mem t
345         imem = (truncate tmem) - nmem - xmem - fmem
346     in
347       if off
348          then printf " - %-*s %57s %3d %3d"
349               mname (name t) "" pl sl
350          else
351              printf " %c %-*s %5.0f %5d %5d %5d %5d %5d %5.0f %5d\
352                     \ %4.0f %4d %3d %3d %6.4f %6.4f %5.2f"
353                  (if off then '-' else if fn then '*' else ' ')
354                  mname (name t) tmem nmem imem xmem fmem (r_mem t)
355                  ((t_dsk t) / 1024) ((f_dsk t) `div` 1024)
356                  (t_cpu t) (u_cpu t)
357                  pl sl mp dp cp