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