Small changes to the node list output
[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            plist, slist, offline)
34     , List
35     -- * Constructor
36     , create
37     -- ** Finalization after data loading
38     , buildPeers
39     , setIdx
40     , setName
41     , setOffline
42     , setXmem
43     , setFmem
44     , setPri
45     , setSec
46     , addCpus
47     -- * Instance (re)location
48     , removePri
49     , removeSec
50     , addPri
51     , addSec
52     -- * Formatting
53     , list
54     -- * Misc stuff
55     , AssocList
56     , noSecondary
57     ) where
58
59 import Data.List
60 import Text.Printf (printf)
61
62 import qualified Ganeti.HTools.Container as Container
63 import qualified Ganeti.HTools.Instance as Instance
64 import qualified Ganeti.HTools.PeerMap as PeerMap
65
66 import qualified Ganeti.HTools.Types as T
67
68 -- * Type declarations
69
70 -- | The node type.
71 data Node = Node { name  :: String -- ^ The node name
72                  , t_mem :: Double -- ^ Total memory (MiB)
73                  , n_mem :: Int    -- ^ Node memory (MiB)
74                  , f_mem :: Int    -- ^ Free memory (MiB)
75                  , x_mem :: Int    -- ^ Unaccounted memory (MiB)
76                  , t_dsk :: Double -- ^ Total disk space (MiB)
77                  , f_dsk :: Int    -- ^ Free disk space (MiB)
78                  , t_cpu :: Double -- ^ Total CPU count
79                  , u_cpu :: Int    -- ^ Used VCPU count
80                  , plist :: [T.Idx]-- ^ List of primary instance indices
81                  , slist :: [T.Idx]-- ^ List of secondary instance indices
82                  , idx :: T.Ndx    -- ^ Internal index for book-keeping
83                  , peers :: PeerMap.PeerMap -- ^ Pnode to instance mapping
84                  , failN1:: Bool   -- ^ Whether the node has failed n1
85                  , r_mem :: Int    -- ^ Maximum memory needed for
86                                    -- failover by primaries of this node
87                  , p_mem :: Double -- ^ Percent of free memory
88                  , p_dsk :: Double -- ^ Percent of free disk
89                  , p_rem :: Double -- ^ Percent of reserved memory
90                  , p_cpu :: Double -- ^ Ratio of virtual to physical CPUs
91                  , offline :: Bool -- ^ Whether the node should not be used
92                                    -- for allocations and skipped from
93                                    -- score computations
94   } deriving (Show)
95
96 instance T.Element Node where
97     nameOf = name
98     idxOf = idx
99     setName = setName
100     setIdx = setIdx
101
102 -- | A simple name for the int, node association list.
103 type AssocList = [(T.Ndx, Node)]
104
105 -- | A simple name for a node map.
106 type List = Container.Container Node
107
108 -- | Constant node index for a non-moveable instance.
109 noSecondary :: T.Ndx
110 noSecondary = -1
111
112 -- * Initialization functions
113
114 -- | Create a new node.
115 --
116 -- The index and the peers maps are empty, and will be need to be
117 -- update later via the 'setIdx' and 'buildPeers' functions.
118 create :: String -> Double -> Int -> Int -> Double
119        -> Int -> Double -> Bool -> Node
120 create name_init mem_t_init mem_n_init mem_f_init
121        dsk_t_init dsk_f_init cpu_t_init offline_init =
122     Node
123     {
124       name  = name_init,
125       t_mem = mem_t_init,
126       n_mem = mem_n_init,
127       f_mem = mem_f_init,
128       t_dsk = dsk_t_init,
129       f_dsk = dsk_f_init,
130       t_cpu = cpu_t_init,
131       u_cpu = 0,
132       plist = [],
133       slist = [],
134       failN1 = True,
135       idx = -1,
136       peers = PeerMap.empty,
137       r_mem = 0,
138       p_mem = (fromIntegral mem_f_init) / mem_t_init,
139       p_dsk = (fromIntegral dsk_f_init) / dsk_t_init,
140       p_rem = 0,
141       p_cpu = 0,
142       offline = offline_init,
143       x_mem = 0
144     }
145
146 -- | Changes the index.
147 --
148 -- This is used only during the building of the data structures.
149 setIdx :: Node -> T.Ndx -> Node
150 setIdx t i = t {idx = i}
151
152 -- | Changes the name.
153 --
154 -- This is used only during the building of the data structures.
155 setName :: Node -> String -> Node
156 setName t s = t {name = s}
157
158 -- | Sets the offline attribute.
159 setOffline :: Node -> Bool -> Node
160 setOffline t val = t { offline = val }
161
162 -- | Sets the unnaccounted memory.
163 setXmem :: Node -> Int -> Node
164 setXmem t val = t { x_mem = val }
165
166 -- | Computes the maximum reserved memory for peers from a peer map.
167 computeMaxRes :: PeerMap.PeerMap -> PeerMap.Elem
168 computeMaxRes new_peers = PeerMap.maxElem new_peers
169
170 -- | Builds the peer map for a given node.
171 buildPeers :: Node -> Instance.List -> Node
172 buildPeers t il =
173     let mdata = map
174                 (\i_idx -> let inst = Container.find i_idx il
175                            in (Instance.pnode inst, Instance.mem inst))
176                 (slist t)
177         pmap = PeerMap.accumArray (+) mdata
178         new_rmem = computeMaxRes pmap
179         new_failN1 = computeFailN1 new_rmem (f_mem t) (f_dsk t)
180         new_prem = (fromIntegral new_rmem) / (t_mem t)
181     in t {peers=pmap, failN1 = new_failN1, r_mem = new_rmem, p_rem = new_prem}
182
183 -- | Assigns an instance to a node as primary without other updates.
184 setPri :: Node -> T.Idx -> Node
185 setPri t idx = t { plist = idx:(plist t) }
186
187 -- | Assigns an instance to a node as secondary without other updates.
188 setSec :: Node -> T.Idx -> Node
189 setSec t idx = t { slist = idx:(slist t) }
190
191 -- | Add primary cpus to a node
192 addCpus :: Node -> Int -> Node
193 addCpus t count =
194     let new_count = (u_cpu t) + count
195     in t { u_cpu = new_count, p_cpu = (fromIntegral new_count) / (t_cpu t) }
196
197 -- * Update functions
198
199 -- | Sets the free memory.
200 setFmem :: Node -> Int -> Node
201 setFmem t new_mem =
202     let new_n1 = computeFailN1 (r_mem t) new_mem (f_dsk t)
203         new_mp = (fromIntegral new_mem) / (t_mem t)
204     in
205       t { f_mem = new_mem, failN1 = new_n1, p_mem = new_mp }
206
207 -- | Given the rmem, free memory and disk, computes the failn1 status.
208 computeFailN1 :: Int -> Int -> Int -> Bool
209 computeFailN1 new_rmem new_mem new_dsk =
210     new_mem <= new_rmem || new_dsk <= 0
211
212 -- | Given the new free memory and disk, fail if any of them is below zero.
213 failHealth :: Int -> Int -> Bool
214 failHealth new_mem new_dsk = new_mem <= 0 || new_dsk <= 0
215
216 -- | Removes a primary instance.
217 removePri :: Node -> Instance.Instance -> Node
218 removePri t inst =
219     let iname = Instance.idx inst
220         new_plist = delete iname (plist t)
221         new_mem = f_mem t + Instance.mem inst
222         new_dsk = f_dsk t + Instance.dsk inst
223         new_mp = (fromIntegral new_mem) / (t_mem t)
224         new_dp = (fromIntegral new_dsk) / (t_dsk t)
225         new_failn1 = computeFailN1 (r_mem t) new_mem new_dsk
226         new_ucpu = (u_cpu t) - (Instance.vcpus inst)
227         new_rcpu = (fromIntegral new_ucpu) / (t_cpu t)
228     in t {plist = new_plist, f_mem = new_mem, f_dsk = new_dsk,
229           failN1 = new_failn1, p_mem = new_mp, p_dsk = new_dp,
230           u_cpu = new_ucpu, p_cpu = new_rcpu}
231
232 -- | Removes a secondary instance.
233 removeSec :: Node -> Instance.Instance -> Node
234 removeSec t inst =
235     let iname = Instance.idx inst
236         pnode = Instance.pnode inst
237         new_slist = delete iname (slist t)
238         new_dsk = f_dsk t + Instance.dsk inst
239         old_peers = peers t
240         old_peem = PeerMap.find pnode old_peers
241         new_peem =  old_peem - (Instance.mem inst)
242         new_peers = PeerMap.add pnode new_peem old_peers
243         old_rmem = r_mem t
244         new_rmem = if old_peem < old_rmem then
245                        old_rmem
246                    else
247                        computeMaxRes new_peers
248         new_prem = (fromIntegral new_rmem) / (t_mem t)
249         new_failn1 = computeFailN1 new_rmem (f_mem t) new_dsk
250         new_dp = (fromIntegral new_dsk) / (t_dsk t)
251     in t {slist = new_slist, f_dsk = new_dsk, peers = new_peers,
252           failN1 = new_failn1, r_mem = new_rmem, p_dsk = new_dp,
253           p_rem = new_prem}
254
255 -- | Adds a primary instance.
256 addPri :: Node -> Instance.Instance -> Maybe Node
257 addPri t inst =
258     let iname = Instance.idx inst
259         new_mem = f_mem t - Instance.mem inst
260         new_dsk = f_dsk t - Instance.dsk inst
261         new_failn1 = computeFailN1 (r_mem t) new_mem new_dsk
262         new_ucpu = (u_cpu t) + (Instance.vcpus inst)
263         new_pcpu = (fromIntegral new_ucpu) / (t_cpu t)
264     in
265       if (failHealth new_mem new_dsk) || (new_failn1 && not (failN1 t)) then
266         Nothing
267       else
268         let new_plist = iname:(plist t)
269             new_mp = (fromIntegral new_mem) / (t_mem t)
270             new_dp = (fromIntegral new_dsk) / (t_dsk t)
271         in
272         Just t {plist = new_plist, f_mem = new_mem, f_dsk = new_dsk,
273                 failN1 = new_failn1, p_mem = new_mp, p_dsk = new_dp,
274                 u_cpu = new_ucpu, p_cpu = new_pcpu}
275
276 -- | Adds a secondary instance.
277 addSec :: Node -> Instance.Instance -> T.Ndx -> Maybe Node
278 addSec t inst pdx =
279     let iname = Instance.idx inst
280         old_peers = peers t
281         old_mem = f_mem t
282         new_dsk = f_dsk t - Instance.dsk inst
283         new_peem = PeerMap.find pdx old_peers + Instance.mem inst
284         new_peers = PeerMap.add pdx new_peem old_peers
285         new_rmem = max (r_mem t) new_peem
286         new_prem = (fromIntegral new_rmem) / (t_mem t)
287         new_failn1 = computeFailN1 new_rmem old_mem new_dsk in
288     if (failHealth old_mem new_dsk) || (new_failn1 && not (failN1 t)) then
289         Nothing
290     else
291         let new_slist = iname:(slist t)
292             new_dp = (fromIntegral new_dsk) / (t_dsk t)
293         in
294         Just t {slist = new_slist, f_dsk = new_dsk,
295                 peers = new_peers, failN1 = new_failn1,
296                 r_mem = new_rmem, p_dsk = new_dp,
297                 p_rem = new_prem}
298
299 -- * Display functions
300
301 -- | String converter for the node list functionality.
302 list :: Int -> Node -> String
303 list mname t =
304     let pl = length $ plist t
305         sl = length $ slist t
306         mp = p_mem t
307         dp = p_dsk t
308         cp = p_cpu t
309         off = offline t
310         fn = failN1 t
311         tmem = t_mem t
312         nmem = n_mem t
313         xmem = x_mem t
314         fmem = f_mem t
315         imem = (truncate tmem) - nmem - xmem - fmem
316     in
317       if off
318          then printf " - %-*s %57s %3d %3d"
319               mname (name t) "" pl sl
320          else
321              printf " %c %-*s %5.0f %5d %5d %5d %5d %5d %5.0f %5d\
322                     \ %4.0f %4d %3d %3d %6.4f %6.4f %5.2f"
323                  (if off then '-' else if fn then '*' else ' ')
324                  mname (name t) tmem nmem imem xmem fmem (r_mem t)
325                  ((t_dsk t) / 1024) ((f_dsk t) `div` 1024)
326                  (t_cpu t) (u_cpu t)
327                  pl sl mp dp cp