Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Node.hs @ f3f76ccc

History | View | Annotate | Download (19.8 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 425af248 Iustin Pop
Copyright (C) 2009, 2010, 2011 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 fd7a7c73 Iustin Pop
  ( Node(..)
30 fd7a7c73 Iustin Pop
  , List
31 fd7a7c73 Iustin Pop
  -- * Constructor
32 fd7a7c73 Iustin Pop
  , create
33 fd7a7c73 Iustin Pop
  -- ** Finalization after data loading
34 fd7a7c73 Iustin Pop
  , buildPeers
35 fd7a7c73 Iustin Pop
  , setIdx
36 fd7a7c73 Iustin Pop
  , setAlias
37 fd7a7c73 Iustin Pop
  , setOffline
38 fd7a7c73 Iustin Pop
  , setXmem
39 fd7a7c73 Iustin Pop
  , setFmem
40 fd7a7c73 Iustin Pop
  , setPri
41 fd7a7c73 Iustin Pop
  , setSec
42 fd7a7c73 Iustin Pop
  , setMdsk
43 fd7a7c73 Iustin Pop
  , setMcpu
44 fd7a7c73 Iustin Pop
  -- * Tag maps
45 fd7a7c73 Iustin Pop
  , addTags
46 fd7a7c73 Iustin Pop
  , delTags
47 fd7a7c73 Iustin Pop
  , rejectAddTags
48 fd7a7c73 Iustin Pop
  -- * Instance (re)location
49 fd7a7c73 Iustin Pop
  , removePri
50 fd7a7c73 Iustin Pop
  , removeSec
51 fd7a7c73 Iustin Pop
  , addPri
52 fd7a7c73 Iustin Pop
  , addPriEx
53 fd7a7c73 Iustin Pop
  , addSec
54 fd7a7c73 Iustin Pop
  , addSecEx
55 fd7a7c73 Iustin Pop
  -- * Stats
56 fd7a7c73 Iustin Pop
  , availDisk
57 fd7a7c73 Iustin Pop
  , availMem
58 fd7a7c73 Iustin Pop
  , availCpu
59 fd7a7c73 Iustin Pop
  , iMem
60 fd7a7c73 Iustin Pop
  , iDsk
61 fd7a7c73 Iustin Pop
  , conflictingPrimaries
62 fd7a7c73 Iustin Pop
  -- * Formatting
63 fd7a7c73 Iustin Pop
  , defaultFields
64 fd7a7c73 Iustin Pop
  , showHeader
65 fd7a7c73 Iustin Pop
  , showField
66 fd7a7c73 Iustin Pop
  , list
67 fd7a7c73 Iustin Pop
  -- * Misc stuff
68 fd7a7c73 Iustin Pop
  , AssocList
69 fd7a7c73 Iustin Pop
  , AllocElement
70 fd7a7c73 Iustin Pop
  , noSecondary
71 fd7a7c73 Iustin Pop
  , computeGroups
72 fd7a7c73 Iustin Pop
  ) where
73 e4f08c46 Iustin Pop
74 a68004b7 Iustin Pop
import Data.List hiding (group)
75 5f0b9579 Iustin Pop
import qualified Data.Map as Map
76 1e4b5230 Iustin Pop
import qualified Data.Foldable as Foldable
77 d8bcd0a8 Iustin Pop
import Data.Ord (comparing)
78 e4f08c46 Iustin Pop
import Text.Printf (printf)
79 e4f08c46 Iustin Pop
80 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Container as Container
81 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
82 12e6776a Iustin Pop
import qualified Ganeti.HTools.PeerMap as P
83 e4f08c46 Iustin Pop
84 262a08a2 Iustin Pop
import qualified Ganeti.HTools.Types as T
85 262a08a2 Iustin Pop
86 9188aeef Iustin Pop
-- * Type declarations
87 9188aeef Iustin Pop
88 525bfb36 Iustin Pop
-- | The tag map type.
89 5f0b9579 Iustin Pop
type TagMap = Map.Map String Int
90 5f0b9579 Iustin Pop
91 9188aeef Iustin Pop
-- | The node type.
92 12e6776a Iustin Pop
data Node = Node
93 fd7a7c73 Iustin Pop
  { name     :: String    -- ^ The node name
94 fd7a7c73 Iustin Pop
  , alias    :: String    -- ^ The shortened name (for display purposes)
95 fd7a7c73 Iustin Pop
  , tMem     :: Double    -- ^ Total memory (MiB)
96 fd7a7c73 Iustin Pop
  , nMem     :: Int       -- ^ Node memory (MiB)
97 fd7a7c73 Iustin Pop
  , fMem     :: Int       -- ^ Free memory (MiB)
98 fd7a7c73 Iustin Pop
  , xMem     :: Int       -- ^ Unaccounted memory (MiB)
99 fd7a7c73 Iustin Pop
  , tDsk     :: Double    -- ^ Total disk space (MiB)
100 fd7a7c73 Iustin Pop
  , fDsk     :: Int       -- ^ Free disk space (MiB)
101 fd7a7c73 Iustin Pop
  , tCpu     :: Double    -- ^ Total CPU count
102 fd7a7c73 Iustin Pop
  , uCpu     :: Int       -- ^ Used VCPU count
103 fd7a7c73 Iustin Pop
  , pList    :: [T.Idx]   -- ^ List of primary instance indices
104 fd7a7c73 Iustin Pop
  , sList    :: [T.Idx]   -- ^ List of secondary instance indices
105 fd7a7c73 Iustin Pop
  , idx      :: T.Ndx     -- ^ Internal index for book-keeping
106 fd7a7c73 Iustin Pop
  , peers    :: P.PeerMap -- ^ Pnode to instance mapping
107 fd7a7c73 Iustin Pop
  , failN1   :: Bool      -- ^ Whether the node has failed n1
108 fd7a7c73 Iustin Pop
  , rMem     :: Int       -- ^ Maximum memory needed for failover by
109 fd7a7c73 Iustin Pop
                          -- primaries of this node
110 fd7a7c73 Iustin Pop
  , pMem     :: Double    -- ^ Percent of free memory
111 fd7a7c73 Iustin Pop
  , pDsk     :: Double    -- ^ Percent of free disk
112 fd7a7c73 Iustin Pop
  , pRem     :: Double    -- ^ Percent of reserved memory
113 fd7a7c73 Iustin Pop
  , pCpu     :: Double    -- ^ Ratio of virtual to physical CPUs
114 fd7a7c73 Iustin Pop
  , mDsk     :: Double    -- ^ Minimum free disk ratio
115 fd7a7c73 Iustin Pop
  , mCpu     :: Double    -- ^ Max ratio of virt-to-phys CPUs
116 fd7a7c73 Iustin Pop
  , loDsk    :: Int       -- ^ Autocomputed from mDsk low disk
117 fd7a7c73 Iustin Pop
                          -- threshold
118 fd7a7c73 Iustin Pop
  , hiCpu    :: Int       -- ^ Autocomputed from mCpu high cpu
119 fd7a7c73 Iustin Pop
                          -- threshold
120 fd7a7c73 Iustin Pop
  , offline  :: Bool      -- ^ Whether the node should not be used for
121 fd7a7c73 Iustin Pop
                          -- allocations and skipped from score
122 fd7a7c73 Iustin Pop
                          -- computations
123 fd7a7c73 Iustin Pop
  , utilPool :: T.DynUtil -- ^ Total utilisation capacity
124 fd7a7c73 Iustin Pop
  , utilLoad :: T.DynUtil -- ^ Sum of instance utilisation
125 fd7a7c73 Iustin Pop
  , pTags    :: TagMap    -- ^ Map of primary instance tags and their count
126 fd7a7c73 Iustin Pop
  , group    :: T.Gdx     -- ^ The node's group (index)
127 fd7a7c73 Iustin Pop
  } deriving (Show, Read, Eq)
128 e4f08c46 Iustin Pop
129 262a08a2 Iustin Pop
instance T.Element Node where
130 fd7a7c73 Iustin Pop
  nameOf = name
131 fd7a7c73 Iustin Pop
  idxOf = idx
132 fd7a7c73 Iustin Pop
  setAlias = setAlias
133 fd7a7c73 Iustin Pop
  setIdx = setIdx
134 fd7a7c73 Iustin Pop
  allNames n = [name n, alias n]
135 262a08a2 Iustin Pop
136 9188aeef Iustin Pop
-- | A simple name for the int, node association list.
137 608efcce Iustin Pop
type AssocList = [(T.Ndx, Node)]
138 040afc35 Iustin Pop
139 9188aeef Iustin Pop
-- | A simple name for a node map.
140 262a08a2 Iustin Pop
type List = Container.Container Node
141 262a08a2 Iustin Pop
142 1fe81531 Iustin Pop
-- | A simple name for an allocation element (here just for logistic
143 525bfb36 Iustin Pop
-- reasons).
144 7d3f4253 Iustin Pop
type AllocElement = (List, Instance.Instance, [Node], T.Score)
145 1fe81531 Iustin Pop
146 9188aeef Iustin Pop
-- | Constant node index for a non-moveable instance.
147 608efcce Iustin Pop
noSecondary :: T.Ndx
148 040afc35 Iustin Pop
noSecondary = -1
149 040afc35 Iustin Pop
150 5f0b9579 Iustin Pop
-- * Helper functions
151 5f0b9579 Iustin Pop
152 525bfb36 Iustin Pop
-- | Add a tag to a tagmap.
153 5f0b9579 Iustin Pop
addTag :: TagMap -> String -> TagMap
154 5f0b9579 Iustin Pop
addTag t s = Map.insertWith (+) s 1 t
155 5f0b9579 Iustin Pop
156 525bfb36 Iustin Pop
-- | Add multiple tags.
157 5f0b9579 Iustin Pop
addTags :: TagMap -> [String] -> TagMap
158 5f0b9579 Iustin Pop
addTags = foldl' addTag
159 5f0b9579 Iustin Pop
160 525bfb36 Iustin Pop
-- | Adjust or delete a tag from a tagmap.
161 5f0b9579 Iustin Pop
delTag :: TagMap -> String -> TagMap
162 5f0b9579 Iustin Pop
delTag t s = Map.update (\v -> if v > 1
163 fd7a7c73 Iustin Pop
                                 then Just (v-1)
164 fd7a7c73 Iustin Pop
                                 else Nothing)
165 5f0b9579 Iustin Pop
             s t
166 5f0b9579 Iustin Pop
167 525bfb36 Iustin Pop
-- | Remove multiple tags.
168 5f0b9579 Iustin Pop
delTags :: TagMap -> [String] -> TagMap
169 5f0b9579 Iustin Pop
delTags = foldl' delTag
170 5f0b9579 Iustin Pop
171 525bfb36 Iustin Pop
-- | Check if we can add a list of tags to a tagmap.
172 5f0b9579 Iustin Pop
rejectAddTags :: TagMap -> [String] -> Bool
173 5182e970 Iustin Pop
rejectAddTags t = any (`Map.member` t)
174 5f0b9579 Iustin Pop
175 1e4b5230 Iustin Pop
-- | Check how many primary instances have conflicting tags. The
176 1e4b5230 Iustin Pop
-- algorithm to compute this is to sum the count of all tags, then
177 1e4b5230 Iustin Pop
-- subtract the size of the tag map (since each tag has at least one,
178 1e4b5230 Iustin Pop
-- non-conflicting instance); this is equivalent to summing the
179 1e4b5230 Iustin Pop
-- values in the tag map minus one.
180 1e4b5230 Iustin Pop
conflictingPrimaries :: Node -> Int
181 1e4b5230 Iustin Pop
conflictingPrimaries (Node { pTags = t }) = Foldable.sum t - Map.size t
182 1e4b5230 Iustin Pop
183 9188aeef Iustin Pop
-- * Initialization functions
184 e4f08c46 Iustin Pop
185 9188aeef Iustin Pop
-- | Create a new node.
186 9188aeef Iustin Pop
--
187 9188aeef Iustin Pop
-- The index and the peers maps are empty, and will be need to be
188 9188aeef Iustin Pop
-- update later via the 'setIdx' and 'buildPeers' functions.
189 1a82215d Iustin Pop
create :: String -> Double -> Int -> Int -> Double
190 10ef6b4e Iustin Pop
       -> Int -> Double -> Bool -> T.Gdx -> Node
191 2727257a Iustin Pop
create name_init mem_t_init mem_n_init mem_f_init
192 a68004b7 Iustin Pop
       dsk_t_init dsk_f_init cpu_t_init offline_init group_init =
193 fd7a7c73 Iustin Pop
  Node { name = name_init
194 fd7a7c73 Iustin Pop
       , alias = name_init
195 fd7a7c73 Iustin Pop
       , tMem = mem_t_init
196 fd7a7c73 Iustin Pop
       , nMem = mem_n_init
197 fd7a7c73 Iustin Pop
       , fMem = mem_f_init
198 fd7a7c73 Iustin Pop
       , tDsk = dsk_t_init
199 fd7a7c73 Iustin Pop
       , fDsk = dsk_f_init
200 fd7a7c73 Iustin Pop
       , tCpu = cpu_t_init
201 fd7a7c73 Iustin Pop
       , uCpu = 0
202 fd7a7c73 Iustin Pop
       , pList = []
203 fd7a7c73 Iustin Pop
       , sList = []
204 fd7a7c73 Iustin Pop
       , failN1 = True
205 fd7a7c73 Iustin Pop
       , idx = -1
206 fd7a7c73 Iustin Pop
       , peers = P.empty
207 fd7a7c73 Iustin Pop
       , rMem = 0
208 fd7a7c73 Iustin Pop
       , pMem = fromIntegral mem_f_init / mem_t_init
209 fd7a7c73 Iustin Pop
       , pDsk = fromIntegral dsk_f_init / dsk_t_init
210 fd7a7c73 Iustin Pop
       , pRem = 0
211 fd7a7c73 Iustin Pop
       , pCpu = 0
212 fd7a7c73 Iustin Pop
       , offline = offline_init
213 fd7a7c73 Iustin Pop
       , xMem = 0
214 fd7a7c73 Iustin Pop
       , mDsk = T.defReservedDiskRatio
215 fd7a7c73 Iustin Pop
       , mCpu = T.defVcpuRatio
216 fd7a7c73 Iustin Pop
       , loDsk = mDskToloDsk T.defReservedDiskRatio dsk_t_init
217 fd7a7c73 Iustin Pop
       , hiCpu = mCpuTohiCpu T.defVcpuRatio cpu_t_init
218 fd7a7c73 Iustin Pop
       , utilPool = T.baseUtil
219 fd7a7c73 Iustin Pop
       , utilLoad = T.zeroUtil
220 fd7a7c73 Iustin Pop
       , pTags = Map.empty
221 fd7a7c73 Iustin Pop
       , group = group_init
222 fd7a7c73 Iustin Pop
       }
223 e4f08c46 Iustin Pop
224 525bfb36 Iustin Pop
-- | Conversion formula from mDsk\/tDsk to loDsk.
225 f4c0b8c5 Iustin Pop
mDskToloDsk :: Double -> Double -> Int
226 05ff7a00 Agata Murawska
mDskToloDsk mval = floor . (mval *)
227 f4c0b8c5 Iustin Pop
228 525bfb36 Iustin Pop
-- | Conversion formula from mCpu\/tCpu to hiCpu.
229 f4c0b8c5 Iustin Pop
mCpuTohiCpu :: Double -> Double -> Int
230 05ff7a00 Agata Murawska
mCpuTohiCpu mval = floor . (mval *)
231 f4c0b8c5 Iustin Pop
232 e4f08c46 Iustin Pop
-- | Changes the index.
233 9188aeef Iustin Pop
--
234 e4f08c46 Iustin Pop
-- This is used only during the building of the data structures.
235 608efcce Iustin Pop
setIdx :: Node -> T.Ndx -> Node
236 e4f08c46 Iustin Pop
setIdx t i = t {idx = i}
237 e4f08c46 Iustin Pop
238 8bcdde0c Iustin Pop
-- | Changes the alias.
239 8bcdde0c Iustin Pop
--
240 8bcdde0c Iustin Pop
-- This is used only during the building of the data structures.
241 8bcdde0c Iustin Pop
setAlias :: Node -> String -> Node
242 8bcdde0c Iustin Pop
setAlias t s = t { alias = s }
243 497e30a1 Iustin Pop
244 9188aeef Iustin Pop
-- | Sets the offline attribute.
245 c2c1ef0c Iustin Pop
setOffline :: Node -> Bool -> Node
246 c2c1ef0c Iustin Pop
setOffline t val = t { offline = val }
247 c2c1ef0c Iustin Pop
248 9188aeef Iustin Pop
-- | Sets the unnaccounted memory.
249 8c5b0a0d Iustin Pop
setXmem :: Node -> Int -> Node
250 2060348b Iustin Pop
setXmem t val = t { xMem = val }
251 8c5b0a0d Iustin Pop
252 525bfb36 Iustin Pop
-- | Sets the max disk usage ratio.
253 844eff86 Iustin Pop
setMdsk :: Node -> Double -> Node
254 f4c0b8c5 Iustin Pop
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
255 844eff86 Iustin Pop
256 525bfb36 Iustin Pop
-- | Sets the max cpu usage ratio.
257 844eff86 Iustin Pop
setMcpu :: Node -> Double -> Node
258 f4c0b8c5 Iustin Pop
setMcpu t val = t { mCpu = val, hiCpu = mCpuTohiCpu val (tCpu t) }
259 844eff86 Iustin Pop
260 e4f08c46 Iustin Pop
-- | Computes the maximum reserved memory for peers from a peer map.
261 12e6776a Iustin Pop
computeMaxRes :: P.PeerMap -> P.Elem
262 12e6776a Iustin Pop
computeMaxRes = P.maxElem
263 e4f08c46 Iustin Pop
264 e4f08c46 Iustin Pop
-- | Builds the peer map for a given node.
265 9cf4267a Iustin Pop
buildPeers :: Node -> Instance.List -> Node
266 9cf4267a Iustin Pop
buildPeers t il =
267 fd7a7c73 Iustin Pop
  let mdata = map
268 fd7a7c73 Iustin Pop
              (\i_idx -> let inst = Container.find i_idx il
269 fd7a7c73 Iustin Pop
                             mem = if Instance.autoBalance inst
270 929b60d8 Iustin Pop
                                     then Instance.mem inst
271 929b60d8 Iustin Pop
                                     else 0
272 fd7a7c73 Iustin Pop
                         in (Instance.pNode inst, mem))
273 fd7a7c73 Iustin Pop
              (sList t)
274 fd7a7c73 Iustin Pop
      pmap = P.accumArray (+) mdata
275 fd7a7c73 Iustin Pop
      new_rmem = computeMaxRes pmap
276 fd7a7c73 Iustin Pop
      new_failN1 = fMem t <= new_rmem
277 fd7a7c73 Iustin Pop
      new_prem = fromIntegral new_rmem / tMem t
278 fd7a7c73 Iustin Pop
  in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
279 e4f08c46 Iustin Pop
280 a488a217 Iustin Pop
-- | Assigns an instance to a node as primary and update the used VCPU
281 5f0b9579 Iustin Pop
-- count, utilisation data and tags map.
282 a488a217 Iustin Pop
setPri :: Node -> Instance.Instance -> Node
283 aa8d2e71 Iustin Pop
setPri t inst = t { pList = Instance.idx inst:pList t
284 a488a217 Iustin Pop
                  , uCpu = new_count
285 aa8d2e71 Iustin Pop
                  , pCpu = fromIntegral new_count / tCpu t
286 aa8d2e71 Iustin Pop
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
287 5f0b9579 Iustin Pop
                  , pTags = addTags (pTags t) (Instance.tags inst)
288 aa8d2e71 Iustin Pop
                  }
289 fd7a7c73 Iustin Pop
  where new_count = uCpu t + Instance.vcpus inst
290 9188aeef Iustin Pop
291 9188aeef Iustin Pop
-- | Assigns an instance to a node as secondary without other updates.
292 a488a217 Iustin Pop
setSec :: Node -> Instance.Instance -> Node
293 aa8d2e71 Iustin Pop
setSec t inst = t { sList = Instance.idx inst:sList t
294 aa8d2e71 Iustin Pop
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
295 aa8d2e71 Iustin Pop
                                          T.dskWeight (Instance.util inst) }
296 aa8d2e71 Iustin Pop
                  }
297 fd7a7c73 Iustin Pop
  where old_load = utilLoad t
298 1a82215d Iustin Pop
299 9188aeef Iustin Pop
-- * Update functions
300 9188aeef Iustin Pop
301 9188aeef Iustin Pop
-- | Sets the free memory.
302 9188aeef Iustin Pop
setFmem :: Node -> Int -> Node
303 9188aeef Iustin Pop
setFmem t new_mem =
304 fd7a7c73 Iustin Pop
  let new_n1 = new_mem <= rMem t
305 fd7a7c73 Iustin Pop
      new_mp = fromIntegral new_mem / tMem t
306 fd7a7c73 Iustin Pop
  in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
307 9188aeef Iustin Pop
308 e4f08c46 Iustin Pop
-- | Removes a primary instance.
309 e4f08c46 Iustin Pop
removePri :: Node -> Instance.Instance -> Node
310 e4f08c46 Iustin Pop
removePri t inst =
311 fd7a7c73 Iustin Pop
  let iname = Instance.idx inst
312 fd7a7c73 Iustin Pop
      new_plist = delete iname (pList t)
313 fd7a7c73 Iustin Pop
      new_mem = Instance.applyIfOnline inst (+ Instance.mem inst) (fMem t)
314 fd7a7c73 Iustin Pop
      new_dsk = fDsk t + Instance.dsk inst
315 fd7a7c73 Iustin Pop
      new_mp = fromIntegral new_mem / tMem t
316 fd7a7c73 Iustin Pop
      new_dp = fromIntegral new_dsk / tDsk t
317 fd7a7c73 Iustin Pop
      new_failn1 = new_mem <= rMem t
318 fd7a7c73 Iustin Pop
      new_ucpu = Instance.applyIfOnline inst
319 fd7a7c73 Iustin Pop
                 (\x -> x - Instance.vcpus inst) (uCpu t)
320 fd7a7c73 Iustin Pop
      new_rcpu = fromIntegral new_ucpu / tCpu t
321 fd7a7c73 Iustin Pop
      new_load = utilLoad t `T.subUtil` Instance.util inst
322 fd7a7c73 Iustin Pop
  in t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
323 fd7a7c73 Iustin Pop
       , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
324 fd7a7c73 Iustin Pop
       , uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load
325 fd7a7c73 Iustin Pop
       , pTags = delTags (pTags t) (Instance.tags inst) }
326 e4f08c46 Iustin Pop
327 e4f08c46 Iustin Pop
-- | Removes a secondary instance.
328 e4f08c46 Iustin Pop
removeSec :: Node -> Instance.Instance -> Node
329 e4f08c46 Iustin Pop
removeSec t inst =
330 fd7a7c73 Iustin Pop
  let iname = Instance.idx inst
331 fd7a7c73 Iustin Pop
      cur_dsk = fDsk t
332 fd7a7c73 Iustin Pop
      pnode = Instance.pNode inst
333 fd7a7c73 Iustin Pop
      new_slist = delete iname (sList t)
334 3603605a Iustin Pop
      new_dsk = if Instance.usesLocalStorage inst
335 10f055ac Iustin Pop
                  then cur_dsk + Instance.dsk inst
336 10f055ac Iustin Pop
                  else cur_dsk
337 fd7a7c73 Iustin Pop
      old_peers = peers t
338 fd7a7c73 Iustin Pop
      old_peem = P.find pnode old_peers
339 fd7a7c73 Iustin Pop
      new_peem =  if Instance.autoBalance inst
340 929b60d8 Iustin Pop
                    then old_peem - Instance.mem inst
341 929b60d8 Iustin Pop
                    else old_peem
342 fd7a7c73 Iustin Pop
      new_peers = if new_peem > 0
343 124b7cd7 Iustin Pop
                    then P.add pnode new_peem old_peers
344 124b7cd7 Iustin Pop
                    else P.remove pnode old_peers
345 fd7a7c73 Iustin Pop
      old_rmem = rMem t
346 fd7a7c73 Iustin Pop
      new_rmem = if old_peem < old_rmem
347 bbd8efd2 Iustin Pop
                   then old_rmem
348 bbd8efd2 Iustin Pop
                   else computeMaxRes new_peers
349 fd7a7c73 Iustin Pop
      new_prem = fromIntegral new_rmem / tMem t
350 fd7a7c73 Iustin Pop
      new_failn1 = fMem t <= new_rmem
351 fd7a7c73 Iustin Pop
      new_dp = fromIntegral new_dsk / tDsk t
352 fd7a7c73 Iustin Pop
      old_load = utilLoad t
353 fd7a7c73 Iustin Pop
      new_load = old_load { T.dskWeight = T.dskWeight old_load -
354 fd7a7c73 Iustin Pop
                                          T.dskWeight (Instance.util inst) }
355 fd7a7c73 Iustin Pop
  in t { sList = new_slist, fDsk = new_dsk, peers = new_peers
356 fd7a7c73 Iustin Pop
       , failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
357 fd7a7c73 Iustin Pop
       , pRem = new_prem, utilLoad = new_load }
358 e4f08c46 Iustin Pop
359 3e3c9393 Iustin Pop
-- | Adds a primary instance (basic version).
360 f2280553 Iustin Pop
addPri :: Node -> Instance.Instance -> T.OpResult Node
361 3e3c9393 Iustin Pop
addPri = addPriEx False
362 3e3c9393 Iustin Pop
363 3e3c9393 Iustin Pop
-- | Adds a primary instance (extended version).
364 3e3c9393 Iustin Pop
addPriEx :: Bool               -- ^ Whether to override the N+1 and
365 3e3c9393 Iustin Pop
                               -- other /soft/ checks, useful if we
366 3e3c9393 Iustin Pop
                               -- come from a worse status
367 3e3c9393 Iustin Pop
                               -- (e.g. offline)
368 3e3c9393 Iustin Pop
         -> Node               -- ^ The target node
369 3e3c9393 Iustin Pop
         -> Instance.Instance  -- ^ The instance to add
370 3e3c9393 Iustin Pop
         -> T.OpResult Node    -- ^ The result of the operation,
371 3e3c9393 Iustin Pop
                               -- either the new version of the node
372 3e3c9393 Iustin Pop
                               -- or a failure mode
373 3e3c9393 Iustin Pop
addPriEx force t inst =
374 fd7a7c73 Iustin Pop
  let iname = Instance.idx inst
375 fd7a7c73 Iustin Pop
      uses_disk = Instance.usesLocalStorage inst
376 fd7a7c73 Iustin Pop
      cur_dsk = fDsk t
377 fd7a7c73 Iustin Pop
      new_mem = Instance.applyIfOnline inst
378 fd7a7c73 Iustin Pop
                (\x -> x - Instance.mem inst) (fMem t)
379 fd7a7c73 Iustin Pop
      new_dsk = if uses_disk
380 10f055ac Iustin Pop
                  then cur_dsk - Instance.dsk inst
381 10f055ac Iustin Pop
                  else cur_dsk
382 fd7a7c73 Iustin Pop
      new_failn1 = new_mem <= rMem t
383 fd7a7c73 Iustin Pop
      new_ucpu = Instance.applyIfOnline inst (+ Instance.vcpus inst) (uCpu t)
384 fd7a7c73 Iustin Pop
      new_pcpu = fromIntegral new_ucpu / tCpu t
385 fd7a7c73 Iustin Pop
      new_dp = fromIntegral new_dsk / tDsk t
386 fd7a7c73 Iustin Pop
      l_cpu = mCpu t
387 fd7a7c73 Iustin Pop
      new_load = utilLoad t `T.addUtil` Instance.util inst
388 fd7a7c73 Iustin Pop
      inst_tags = Instance.tags inst
389 fd7a7c73 Iustin Pop
      old_tags = pTags t
390 fd7a7c73 Iustin Pop
      strict = not force
391 fd7a7c73 Iustin Pop
  in case () of
392 fd7a7c73 Iustin Pop
       _ | new_mem <= 0 -> T.OpFail T.FailMem
393 fd7a7c73 Iustin Pop
         | uses_disk && new_dsk <= 0 -> T.OpFail T.FailDisk
394 fd7a7c73 Iustin Pop
         | uses_disk && mDsk t > new_dp && strict -> T.OpFail T.FailDisk
395 fd7a7c73 Iustin Pop
         | new_failn1 && not (failN1 t) && strict -> T.OpFail T.FailMem
396 fd7a7c73 Iustin Pop
         | l_cpu >= 0 && l_cpu < new_pcpu && strict -> T.OpFail T.FailCPU
397 fd7a7c73 Iustin Pop
         | rejectAddTags old_tags inst_tags -> T.OpFail T.FailTags
398 fd7a7c73 Iustin Pop
         | otherwise ->
399 fd7a7c73 Iustin Pop
           let new_plist = iname:pList t
400 fd7a7c73 Iustin Pop
               new_mp = fromIntegral new_mem / tMem t
401 fd7a7c73 Iustin Pop
               r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
402 fd7a7c73 Iustin Pop
                     , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
403 fd7a7c73 Iustin Pop
                     , uCpu = new_ucpu, pCpu = new_pcpu
404 fd7a7c73 Iustin Pop
                     , utilLoad = new_load
405 fd7a7c73 Iustin Pop
                     , pTags = addTags old_tags inst_tags }
406 fd7a7c73 Iustin Pop
           in T.OpGood r
407 e4f08c46 Iustin Pop
408 3e3c9393 Iustin Pop
-- | Adds a secondary instance (basic version).
409 f2280553 Iustin Pop
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
410 3e3c9393 Iustin Pop
addSec = addSecEx False
411 3e3c9393 Iustin Pop
412 3e3c9393 Iustin Pop
-- | Adds a secondary instance (extended version).
413 3e3c9393 Iustin Pop
addSecEx :: Bool -> Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
414 3e3c9393 Iustin Pop
addSecEx force t inst pdx =
415 fd7a7c73 Iustin Pop
  let iname = Instance.idx inst
416 fd7a7c73 Iustin Pop
      old_peers = peers t
417 fd7a7c73 Iustin Pop
      old_mem = fMem t
418 fd7a7c73 Iustin Pop
      new_dsk = fDsk t - Instance.dsk inst
419 fd7a7c73 Iustin Pop
      secondary_needed_mem = if Instance.autoBalance inst &&
420 fd7a7c73 Iustin Pop
                             not (Instance.instanceOffline inst)
421 929b60d8 Iustin Pop
                               then Instance.mem inst
422 929b60d8 Iustin Pop
                               else 0
423 fd7a7c73 Iustin Pop
      new_peem = P.find pdx old_peers + secondary_needed_mem
424 fd7a7c73 Iustin Pop
      new_peers = P.add pdx new_peem old_peers
425 fd7a7c73 Iustin Pop
      new_rmem = max (rMem t) new_peem
426 fd7a7c73 Iustin Pop
      new_prem = fromIntegral new_rmem / tMem t
427 fd7a7c73 Iustin Pop
      new_failn1 = old_mem <= new_rmem
428 fd7a7c73 Iustin Pop
      new_dp = fromIntegral new_dsk / tDsk t
429 fd7a7c73 Iustin Pop
      old_load = utilLoad t
430 fd7a7c73 Iustin Pop
      new_load = old_load { T.dskWeight = T.dskWeight old_load +
431 fd7a7c73 Iustin Pop
                                          T.dskWeight (Instance.util inst) }
432 fd7a7c73 Iustin Pop
      strict = not force
433 fd7a7c73 Iustin Pop
  in case () of
434 fd7a7c73 Iustin Pop
       _ | not (Instance.hasSecondary inst) -> T.OpFail T.FailDisk
435 fd7a7c73 Iustin Pop
         | new_dsk <= 0 -> T.OpFail T.FailDisk
436 fd7a7c73 Iustin Pop
         | mDsk t > new_dp && strict -> T.OpFail T.FailDisk
437 fd7a7c73 Iustin Pop
         | secondary_needed_mem >= old_mem && strict -> T.OpFail T.FailMem
438 fd7a7c73 Iustin Pop
         | new_failn1 && not (failN1 t) && strict -> T.OpFail T.FailMem
439 fd7a7c73 Iustin Pop
         | otherwise ->
440 fd7a7c73 Iustin Pop
           let new_slist = iname:sList t
441 fd7a7c73 Iustin Pop
               r = t { sList = new_slist, fDsk = new_dsk
442 fd7a7c73 Iustin Pop
                     , peers = new_peers, failN1 = new_failn1
443 fd7a7c73 Iustin Pop
                     , rMem = new_rmem, pDsk = new_dp
444 fd7a7c73 Iustin Pop
                     , pRem = new_prem, utilLoad = new_load }
445 fd7a7c73 Iustin Pop
           in T.OpGood r
446 e4f08c46 Iustin Pop
447 fe3d6f02 Iustin Pop
-- * Stats functions
448 fe3d6f02 Iustin Pop
449 525bfb36 Iustin Pop
-- | Computes the amount of available disk on a given node.
450 fe3d6f02 Iustin Pop
availDisk :: Node -> Int
451 fe3d6f02 Iustin Pop
availDisk t =
452 fd7a7c73 Iustin Pop
  let _f = fDsk t
453 fd7a7c73 Iustin Pop
      _l = loDsk t
454 fd7a7c73 Iustin Pop
  in if _f < _l
455 f4c0b8c5 Iustin Pop
       then 0
456 f4c0b8c5 Iustin Pop
       else _f - _l
457 fe3d6f02 Iustin Pop
458 525bfb36 Iustin Pop
-- | Computes the amount of used disk on a given node.
459 55da339e Iustin Pop
iDsk :: Node -> Int
460 55da339e Iustin Pop
iDsk t = truncate (tDsk t) - fDsk t
461 55da339e Iustin Pop
462 525bfb36 Iustin Pop
-- | Computes the amount of available memory on a given node.
463 1e3dccc8 Iustin Pop
availMem :: Node -> Int
464 1e3dccc8 Iustin Pop
availMem t =
465 fd7a7c73 Iustin Pop
  let _f = fMem t
466 fd7a7c73 Iustin Pop
      _l = rMem t
467 fd7a7c73 Iustin Pop
  in if _f < _l
468 1e3dccc8 Iustin Pop
       then 0
469 1e3dccc8 Iustin Pop
       else _f - _l
470 1e3dccc8 Iustin Pop
471 525bfb36 Iustin Pop
-- | Computes the amount of available memory on a given node.
472 1e3dccc8 Iustin Pop
availCpu :: Node -> Int
473 1e3dccc8 Iustin Pop
availCpu t =
474 fd7a7c73 Iustin Pop
  let _u = uCpu t
475 fd7a7c73 Iustin Pop
      _l = hiCpu t
476 fd7a7c73 Iustin Pop
  in if _l >= _u
477 1e3dccc8 Iustin Pop
       then _l - _u
478 1e3dccc8 Iustin Pop
       else 0
479 1e3dccc8 Iustin Pop
480 425af248 Iustin Pop
-- | The memory used by instances on a given node.
481 425af248 Iustin Pop
iMem :: Node -> Int
482 425af248 Iustin Pop
iMem t = truncate (tMem t) - nMem t - xMem t - fMem t
483 425af248 Iustin Pop
484 9188aeef Iustin Pop
-- * Display functions
485 01f6a5d2 Iustin Pop
486 525bfb36 Iustin Pop
-- | Return a field for a given node.
487 525bfb36 Iustin Pop
showField :: Node   -- ^ Node which we're querying
488 525bfb36 Iustin Pop
          -> String -- ^ Field name
489 525bfb36 Iustin Pop
          -> String -- ^ Field value as string
490 c5f7412e Iustin Pop
showField t field =
491 fd7a7c73 Iustin Pop
  case field of
492 fd7a7c73 Iustin Pop
    "idx"  -> printf "%4d" $ idx t
493 fd7a7c73 Iustin Pop
    "name" -> alias t
494 fd7a7c73 Iustin Pop
    "fqdn" -> name t
495 fd7a7c73 Iustin Pop
    "status" -> case () of
496 fd7a7c73 Iustin Pop
                  _ | offline t -> "-"
497 fd7a7c73 Iustin Pop
                    | failN1 t -> "*"
498 fd7a7c73 Iustin Pop
                    | otherwise -> " "
499 fd7a7c73 Iustin Pop
    "tmem" -> printf "%5.0f" $ tMem t
500 fd7a7c73 Iustin Pop
    "nmem" -> printf "%5d" $ nMem t
501 fd7a7c73 Iustin Pop
    "xmem" -> printf "%5d" $ xMem t
502 fd7a7c73 Iustin Pop
    "fmem" -> printf "%5d" $ fMem t
503 fd7a7c73 Iustin Pop
    "imem" -> printf "%5d" $ iMem t
504 fd7a7c73 Iustin Pop
    "rmem" -> printf "%5d" $ rMem t
505 fd7a7c73 Iustin Pop
    "amem" -> printf "%5d" $ fMem t - rMem t
506 fd7a7c73 Iustin Pop
    "tdsk" -> printf "%5.0f" $ tDsk t / 1024
507 fd7a7c73 Iustin Pop
    "fdsk" -> printf "%5d" $ fDsk t `div` 1024
508 fd7a7c73 Iustin Pop
    "tcpu" -> printf "%4.0f" $ tCpu t
509 fd7a7c73 Iustin Pop
    "ucpu" -> printf "%4d" $ uCpu t
510 fd7a7c73 Iustin Pop
    "pcnt" -> printf "%3d" $ length (pList t)
511 fd7a7c73 Iustin Pop
    "scnt" -> printf "%3d" $ length (sList t)
512 fd7a7c73 Iustin Pop
    "plist" -> show $ pList t
513 fd7a7c73 Iustin Pop
    "slist" -> show $ sList t
514 fd7a7c73 Iustin Pop
    "pfmem" -> printf "%6.4f" $ pMem t
515 fd7a7c73 Iustin Pop
    "pfdsk" -> printf "%6.4f" $ pDsk t
516 fd7a7c73 Iustin Pop
    "rcpu"  -> printf "%5.2f" $ pCpu t
517 fd7a7c73 Iustin Pop
    "cload" -> printf "%5.3f" uC
518 fd7a7c73 Iustin Pop
    "mload" -> printf "%5.3f" uM
519 fd7a7c73 Iustin Pop
    "dload" -> printf "%5.3f" uD
520 fd7a7c73 Iustin Pop
    "nload" -> printf "%5.3f" uN
521 fd7a7c73 Iustin Pop
    "ptags" -> intercalate "," . map (uncurry (printf "%s=%d")) .
522 fd7a7c73 Iustin Pop
               Map.toList $ pTags t
523 fd7a7c73 Iustin Pop
    "peermap" -> show $ peers t
524 fd7a7c73 Iustin Pop
    _ -> T.unknownField
525 fd7a7c73 Iustin Pop
  where
526 fd7a7c73 Iustin Pop
    T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
527 fd7a7c73 Iustin Pop
                T.dskWeight = uD, T.netWeight = uN } = utilLoad t
528 c5f7412e Iustin Pop
529 525bfb36 Iustin Pop
-- | Returns the header and numeric propery of a field.
530 76354e11 Iustin Pop
showHeader :: String -> (String, Bool)
531 76354e11 Iustin Pop
showHeader field =
532 fd7a7c73 Iustin Pop
  case field of
533 fd7a7c73 Iustin Pop
    "idx" -> ("Index", True)
534 fd7a7c73 Iustin Pop
    "name" -> ("Name", False)
535 fd7a7c73 Iustin Pop
    "fqdn" -> ("Name", False)
536 fd7a7c73 Iustin Pop
    "status" -> ("F", False)
537 fd7a7c73 Iustin Pop
    "tmem" -> ("t_mem", True)
538 fd7a7c73 Iustin Pop
    "nmem" -> ("n_mem", True)
539 fd7a7c73 Iustin Pop
    "xmem" -> ("x_mem", True)
540 fd7a7c73 Iustin Pop
    "fmem" -> ("f_mem", True)
541 fd7a7c73 Iustin Pop
    "imem" -> ("i_mem", True)
542 fd7a7c73 Iustin Pop
    "rmem" -> ("r_mem", True)
543 fd7a7c73 Iustin Pop
    "amem" -> ("a_mem", True)
544 fd7a7c73 Iustin Pop
    "tdsk" -> ("t_dsk", True)
545 fd7a7c73 Iustin Pop
    "fdsk" -> ("f_dsk", True)
546 fd7a7c73 Iustin Pop
    "tcpu" -> ("pcpu", True)
547 fd7a7c73 Iustin Pop
    "ucpu" -> ("vcpu", True)
548 fd7a7c73 Iustin Pop
    "pcnt" -> ("pcnt", True)
549 fd7a7c73 Iustin Pop
    "scnt" -> ("scnt", True)
550 fd7a7c73 Iustin Pop
    "plist" -> ("primaries", True)
551 fd7a7c73 Iustin Pop
    "slist" -> ("secondaries", True)
552 fd7a7c73 Iustin Pop
    "pfmem" -> ("p_fmem", True)
553 fd7a7c73 Iustin Pop
    "pfdsk" -> ("p_fdsk", True)
554 fd7a7c73 Iustin Pop
    "rcpu"  -> ("r_cpu", True)
555 fd7a7c73 Iustin Pop
    "cload" -> ("lCpu", True)
556 fd7a7c73 Iustin Pop
    "mload" -> ("lMem", True)
557 fd7a7c73 Iustin Pop
    "dload" -> ("lDsk", True)
558 fd7a7c73 Iustin Pop
    "nload" -> ("lNet", True)
559 fd7a7c73 Iustin Pop
    "ptags" -> ("PrimaryTags", False)
560 fd7a7c73 Iustin Pop
    "peermap" -> ("PeerMap", False)
561 fd7a7c73 Iustin Pop
    -- TODO: add node fields (group.uuid, group)
562 fd7a7c73 Iustin Pop
    _ -> (T.unknownField, False)
563 c5f7412e Iustin Pop
564 e4f08c46 Iustin Pop
-- | String converter for the node list functionality.
565 76354e11 Iustin Pop
list :: [String] -> Node -> [String]
566 76354e11 Iustin Pop
list fields t = map (showField t) fields
567 76354e11 Iustin Pop
568 525bfb36 Iustin Pop
-- | Constant holding the fields we're displaying by default.
569 76354e11 Iustin Pop
defaultFields :: [String]
570 76354e11 Iustin Pop
defaultFields =
571 fd7a7c73 Iustin Pop
  [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
572 fd7a7c73 Iustin Pop
  , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
573 fd7a7c73 Iustin Pop
  , "pfmem", "pfdsk", "rcpu"
574 fd7a7c73 Iustin Pop
  , "cload", "mload", "dload", "nload" ]
575 d8bcd0a8 Iustin Pop
576 d8bcd0a8 Iustin Pop
-- | Split a list of nodes into a list of (node group UUID, list of
577 525bfb36 Iustin Pop
-- associated nodes).
578 10ef6b4e Iustin Pop
computeGroups :: [Node] -> [(T.Gdx, [Node])]
579 d8bcd0a8 Iustin Pop
computeGroups nodes =
580 d8bcd0a8 Iustin Pop
  let nodes' = sortBy (comparing group) nodes
581 d8bcd0a8 Iustin Pop
      nodes'' = groupBy (\a b -> group a == group b) nodes'
582 d8bcd0a8 Iustin Pop
  in map (\nl -> (group (head nl), nl)) nodes''