Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Node.hs @ 9f13be88

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