Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Node.hs @ e817723c

History | View | Annotate | Download (28.9 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 72747d91 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 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 6c332a37 Klaus Aehlig
  , setMaster
43 07ea9bf5 Klaus Aehlig
  , setNodeTags
44 fd7a7c73 Iustin Pop
  , setMdsk
45 fd7a7c73 Iustin Pop
  , setMcpu
46 d6eec019 Iustin Pop
  , setPolicy
47 fd7a7c73 Iustin Pop
  -- * Tag maps
48 fd7a7c73 Iustin Pop
  , addTags
49 fd7a7c73 Iustin Pop
  , delTags
50 fd7a7c73 Iustin Pop
  , rejectAddTags
51 fd7a7c73 Iustin Pop
  -- * Instance (re)location
52 fd7a7c73 Iustin Pop
  , removePri
53 fd7a7c73 Iustin Pop
  , removeSec
54 fd7a7c73 Iustin Pop
  , addPri
55 fd7a7c73 Iustin Pop
  , addPriEx
56 fd7a7c73 Iustin Pop
  , addSec
57 fd7a7c73 Iustin Pop
  , addSecEx
58 fd7a7c73 Iustin Pop
  -- * Stats
59 fd7a7c73 Iustin Pop
  , availDisk
60 fd7a7c73 Iustin Pop
  , availMem
61 fd7a7c73 Iustin Pop
  , availCpu
62 fd7a7c73 Iustin Pop
  , iMem
63 fd7a7c73 Iustin Pop
  , iDsk
64 fd7a7c73 Iustin Pop
  , conflictingPrimaries
65 fd7a7c73 Iustin Pop
  -- * Formatting
66 fd7a7c73 Iustin Pop
  , defaultFields
67 fd7a7c73 Iustin Pop
  , showHeader
68 fd7a7c73 Iustin Pop
  , showField
69 fd7a7c73 Iustin Pop
  , list
70 fd7a7c73 Iustin Pop
  -- * Misc stuff
71 fd7a7c73 Iustin Pop
  , AssocList
72 fd7a7c73 Iustin Pop
  , AllocElement
73 fd7a7c73 Iustin Pop
  , noSecondary
74 fd7a7c73 Iustin Pop
  , computeGroups
75 dae1f9cb Guido Trotter
  , mkNodeGraph
76 30fded87 Klaus Aehlig
  , mkRebootNodeGraph
77 0cc3d742 Bernardo Dal Seno
  , haveExclStorage
78 fd7a7c73 Iustin Pop
  ) where
79 e4f08c46 Iustin Pop
80 86aa9ba3 Iustin Pop
import Control.Monad (liftM, liftM2)
81 30fded87 Klaus Aehlig
import Control.Applicative ((<$>), (<*>))
82 1e4b5230 Iustin Pop
import qualified Data.Foldable as Foldable
83 86aa9ba3 Iustin Pop
import Data.Function (on)
84 dae1f9cb Guido Trotter
import qualified Data.Graph as Graph
85 86aa9ba3 Iustin Pop
import qualified Data.IntMap as IntMap
86 86aa9ba3 Iustin Pop
import Data.List hiding (group)
87 86aa9ba3 Iustin Pop
import qualified Data.Map as Map
88 d8bcd0a8 Iustin Pop
import Data.Ord (comparing)
89 e4f08c46 Iustin Pop
import Text.Printf (printf)
90 e4f08c46 Iustin Pop
91 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Container as Container
92 669d7e3d Iustin Pop
import qualified Ganeti.HTools.Instance as Instance
93 12e6776a Iustin Pop
import qualified Ganeti.HTools.PeerMap as P
94 e4f08c46 Iustin Pop
95 a8038349 Iustin Pop
import Ganeti.BasicTypes
96 262a08a2 Iustin Pop
import qualified Ganeti.HTools.Types as T
97 262a08a2 Iustin Pop
98 9188aeef Iustin Pop
-- * Type declarations
99 9188aeef Iustin Pop
100 525bfb36 Iustin Pop
-- | The tag map type.
101 5f0b9579 Iustin Pop
type TagMap = Map.Map String Int
102 5f0b9579 Iustin Pop
103 9188aeef Iustin Pop
-- | The node type.
104 12e6776a Iustin Pop
data Node = Node
105 fd7a7c73 Iustin Pop
  { name     :: String    -- ^ The node name
106 fd7a7c73 Iustin Pop
  , alias    :: String    -- ^ The shortened name (for display purposes)
107 fd7a7c73 Iustin Pop
  , tMem     :: Double    -- ^ Total memory (MiB)
108 fd7a7c73 Iustin Pop
  , nMem     :: Int       -- ^ Node memory (MiB)
109 fd7a7c73 Iustin Pop
  , fMem     :: Int       -- ^ Free memory (MiB)
110 fd7a7c73 Iustin Pop
  , xMem     :: Int       -- ^ Unaccounted memory (MiB)
111 fd7a7c73 Iustin Pop
  , tDsk     :: Double    -- ^ Total disk space (MiB)
112 fd7a7c73 Iustin Pop
  , fDsk     :: Int       -- ^ Free disk space (MiB)
113 fd7a7c73 Iustin Pop
  , tCpu     :: Double    -- ^ Total CPU count
114 c8c071cb Bernardo Dal Seno
  , nCpu     :: Int       -- ^ VCPUs used by the node OS
115 fd7a7c73 Iustin Pop
  , uCpu     :: Int       -- ^ Used VCPU count
116 96f9b0a6 Bernardo Dal Seno
  , tSpindles :: Int      -- ^ Node spindles (spindle_count node parameter,
117 96f9b0a6 Bernardo Dal Seno
                          -- or actual spindles, see note below)
118 96f9b0a6 Bernardo Dal Seno
  , fSpindles :: Int      -- ^ Free spindles (see note below)
119 fd7a7c73 Iustin Pop
  , pList    :: [T.Idx]   -- ^ List of primary instance indices
120 fd7a7c73 Iustin Pop
  , sList    :: [T.Idx]   -- ^ List of secondary instance indices
121 fd7a7c73 Iustin Pop
  , idx      :: T.Ndx     -- ^ Internal index for book-keeping
122 fd7a7c73 Iustin Pop
  , peers    :: P.PeerMap -- ^ Pnode to instance mapping
123 fd7a7c73 Iustin Pop
  , failN1   :: Bool      -- ^ Whether the node has failed n1
124 fd7a7c73 Iustin Pop
  , rMem     :: Int       -- ^ Maximum memory needed for failover by
125 fd7a7c73 Iustin Pop
                          -- primaries of this node
126 fd7a7c73 Iustin Pop
  , pMem     :: Double    -- ^ Percent of free memory
127 fd7a7c73 Iustin Pop
  , pDsk     :: Double    -- ^ Percent of free disk
128 fd7a7c73 Iustin Pop
  , pRem     :: Double    -- ^ Percent of reserved memory
129 fd7a7c73 Iustin Pop
  , pCpu     :: Double    -- ^ Ratio of virtual to physical CPUs
130 fd7a7c73 Iustin Pop
  , mDsk     :: Double    -- ^ Minimum free disk ratio
131 fd7a7c73 Iustin Pop
  , loDsk    :: Int       -- ^ Autocomputed from mDsk low disk
132 fd7a7c73 Iustin Pop
                          -- threshold
133 fd7a7c73 Iustin Pop
  , hiCpu    :: Int       -- ^ Autocomputed from mCpu high cpu
134 fd7a7c73 Iustin Pop
                          -- threshold
135 96f9b0a6 Bernardo Dal Seno
  , hiSpindles :: Double  -- ^ Limit auto-computed from policy spindle_ratio
136 96f9b0a6 Bernardo Dal Seno
                          -- and the node spindle count (see note below)
137 96f9b0a6 Bernardo Dal Seno
  , instSpindles :: Double -- ^ Spindles used by instances (see note below)
138 fd7a7c73 Iustin Pop
  , offline  :: Bool      -- ^ Whether the node should not be used for
139 fd7a7c73 Iustin Pop
                          -- allocations and skipped from score
140 fd7a7c73 Iustin Pop
                          -- computations
141 6c332a37 Klaus Aehlig
  , isMaster :: Bool      -- ^ Whether the node is the master node
142 07ea9bf5 Klaus Aehlig
  , nTags    :: [String]  -- ^ The node tags for this node
143 fd7a7c73 Iustin Pop
  , utilPool :: T.DynUtil -- ^ Total utilisation capacity
144 fd7a7c73 Iustin Pop
  , utilLoad :: T.DynUtil -- ^ Sum of instance utilisation
145 2f907bad Dato Simรณ
  , pTags    :: TagMap    -- ^ Primary instance exclusion tags and their count
146 fd7a7c73 Iustin Pop
  , group    :: T.Gdx     -- ^ The node's group (index)
147 d6eec019 Iustin Pop
  , iPolicy  :: T.IPolicy -- ^ The instance policy (of the node's group)
148 c324da14 Bernardo Dal Seno
  , exclStorage :: Bool   -- ^ Effective value of exclusive_storage
149 139c0683 Iustin Pop
  } deriving (Show, Eq)
150 96f9b0a6 Bernardo Dal Seno
{- A note on how we handle spindles
151 96f9b0a6 Bernardo Dal Seno
152 96f9b0a6 Bernardo Dal Seno
With exclusive storage spindles is a resource, so we track the number of
153 96f9b0a6 Bernardo Dal Seno
spindles still available (fSpindles). This is the only reliable way, as some
154 96f9b0a6 Bernardo Dal Seno
spindles could be used outside of Ganeti. When exclusive storage is off,
155 96f9b0a6 Bernardo Dal Seno
spindles are a way to represent disk I/O pressure, and hence we track the amount
156 96f9b0a6 Bernardo Dal Seno
used by the instances. We compare it against 'hiSpindles', computed from the
157 96f9b0a6 Bernardo Dal Seno
instance policy, to avoid policy violations. In both cases we store the total
158 96f9b0a6 Bernardo Dal Seno
spindles in 'tSpindles'.
159 96f9b0a6 Bernardo Dal Seno
-}
160 e4f08c46 Iustin Pop
161 262a08a2 Iustin Pop
instance T.Element Node where
162 fd7a7c73 Iustin Pop
  nameOf = name
163 fd7a7c73 Iustin Pop
  idxOf = idx
164 fd7a7c73 Iustin Pop
  setAlias = setAlias
165 fd7a7c73 Iustin Pop
  setIdx = setIdx
166 fd7a7c73 Iustin Pop
  allNames n = [name n, alias n]
167 262a08a2 Iustin Pop
168 9188aeef Iustin Pop
-- | A simple name for the int, node association list.
169 608efcce Iustin Pop
type AssocList = [(T.Ndx, Node)]
170 040afc35 Iustin Pop
171 9188aeef Iustin Pop
-- | A simple name for a node map.
172 262a08a2 Iustin Pop
type List = Container.Container Node
173 262a08a2 Iustin Pop
174 1fe81531 Iustin Pop
-- | A simple name for an allocation element (here just for logistic
175 525bfb36 Iustin Pop
-- reasons).
176 7d3f4253 Iustin Pop
type AllocElement = (List, Instance.Instance, [Node], T.Score)
177 1fe81531 Iustin Pop
178 9188aeef Iustin Pop
-- | Constant node index for a non-moveable instance.
179 608efcce Iustin Pop
noSecondary :: T.Ndx
180 040afc35 Iustin Pop
noSecondary = -1
181 040afc35 Iustin Pop
182 5f0b9579 Iustin Pop
-- * Helper functions
183 5f0b9579 Iustin Pop
184 525bfb36 Iustin Pop
-- | Add a tag to a tagmap.
185 5f0b9579 Iustin Pop
addTag :: TagMap -> String -> TagMap
186 5f0b9579 Iustin Pop
addTag t s = Map.insertWith (+) s 1 t
187 5f0b9579 Iustin Pop
188 525bfb36 Iustin Pop
-- | Add multiple tags.
189 5f0b9579 Iustin Pop
addTags :: TagMap -> [String] -> TagMap
190 5f0b9579 Iustin Pop
addTags = foldl' addTag
191 5f0b9579 Iustin Pop
192 525bfb36 Iustin Pop
-- | Adjust or delete a tag from a tagmap.
193 5f0b9579 Iustin Pop
delTag :: TagMap -> String -> TagMap
194 5f0b9579 Iustin Pop
delTag t s = Map.update (\v -> if v > 1
195 fd7a7c73 Iustin Pop
                                 then Just (v-1)
196 fd7a7c73 Iustin Pop
                                 else Nothing)
197 5f0b9579 Iustin Pop
             s t
198 5f0b9579 Iustin Pop
199 525bfb36 Iustin Pop
-- | Remove multiple tags.
200 5f0b9579 Iustin Pop
delTags :: TagMap -> [String] -> TagMap
201 5f0b9579 Iustin Pop
delTags = foldl' delTag
202 5f0b9579 Iustin Pop
203 525bfb36 Iustin Pop
-- | Check if we can add a list of tags to a tagmap.
204 5f0b9579 Iustin Pop
rejectAddTags :: TagMap -> [String] -> Bool
205 5182e970 Iustin Pop
rejectAddTags t = any (`Map.member` t)
206 5f0b9579 Iustin Pop
207 1e4b5230 Iustin Pop
-- | Check how many primary instances have conflicting tags. The
208 1e4b5230 Iustin Pop
-- algorithm to compute this is to sum the count of all tags, then
209 1e4b5230 Iustin Pop
-- subtract the size of the tag map (since each tag has at least one,
210 1e4b5230 Iustin Pop
-- non-conflicting instance); this is equivalent to summing the
211 1e4b5230 Iustin Pop
-- values in the tag map minus one.
212 1e4b5230 Iustin Pop
conflictingPrimaries :: Node -> Int
213 1e4b5230 Iustin Pop
conflictingPrimaries (Node { pTags = t }) = Foldable.sum t - Map.size t
214 1e4b5230 Iustin Pop
215 f87c9f5d Iustin Pop
-- | Helper function to increment a base value depending on the passed
216 f87c9f5d Iustin Pop
-- boolean argument.
217 f87c9f5d Iustin Pop
incIf :: (Num a) => Bool -> a -> a -> a
218 f87c9f5d Iustin Pop
incIf True  base delta = base + delta
219 f87c9f5d Iustin Pop
incIf False base _     = base
220 f87c9f5d Iustin Pop
221 f87c9f5d Iustin Pop
-- | Helper function to decrement a base value depending on the passed
222 f87c9f5d Iustin Pop
-- boolean argument.
223 f87c9f5d Iustin Pop
decIf :: (Num a) => Bool -> a -> a -> a
224 f87c9f5d Iustin Pop
decIf True  base delta = base - delta
225 f87c9f5d Iustin Pop
decIf False base _     = base
226 f87c9f5d Iustin Pop
227 0cc3d742 Bernardo Dal Seno
-- | Is exclusive storage enabled on any node?
228 0cc3d742 Bernardo Dal Seno
haveExclStorage :: List -> Bool
229 0cc3d742 Bernardo Dal Seno
haveExclStorage nl =
230 0cc3d742 Bernardo Dal Seno
  any exclStorage $ Container.elems nl
231 0cc3d742 Bernardo Dal Seno
232 9188aeef Iustin Pop
-- * Initialization functions
233 e4f08c46 Iustin Pop
234 9188aeef Iustin Pop
-- | Create a new node.
235 9188aeef Iustin Pop
--
236 9188aeef Iustin Pop
-- The index and the peers maps are empty, and will be need to be
237 9188aeef Iustin Pop
-- update later via the 'setIdx' and 'buildPeers' functions.
238 c8c071cb Bernardo Dal Seno
create :: String -> Double -> Int -> Int
239 c8c071cb Bernardo Dal Seno
       -> Double -> Int -> Double -> Int -> Bool
240 c8c071cb Bernardo Dal Seno
       -> Int -> Int -> T.Gdx -> Bool
241 c8c071cb Bernardo Dal Seno
       -> Node
242 2727257a Iustin Pop
create name_init mem_t_init mem_n_init mem_f_init
243 c8c071cb Bernardo Dal Seno
       dsk_t_init dsk_f_init cpu_t_init cpu_n_init offline_init
244 c8c071cb Bernardo Dal Seno
       spindles_t_init spindles_f_init group_init excl_stor =
245 fd7a7c73 Iustin Pop
  Node { name = name_init
246 fd7a7c73 Iustin Pop
       , alias = name_init
247 fd7a7c73 Iustin Pop
       , tMem = mem_t_init
248 fd7a7c73 Iustin Pop
       , nMem = mem_n_init
249 fd7a7c73 Iustin Pop
       , fMem = mem_f_init
250 fd7a7c73 Iustin Pop
       , tDsk = dsk_t_init
251 fd7a7c73 Iustin Pop
       , fDsk = dsk_f_init
252 fd7a7c73 Iustin Pop
       , tCpu = cpu_t_init
253 c8c071cb Bernardo Dal Seno
       , nCpu = cpu_n_init
254 c8c071cb Bernardo Dal Seno
       , uCpu = cpu_n_init
255 96f9b0a6 Bernardo Dal Seno
       , tSpindles = spindles_t_init
256 96f9b0a6 Bernardo Dal Seno
       , fSpindles = spindles_f_init
257 fd7a7c73 Iustin Pop
       , pList = []
258 fd7a7c73 Iustin Pop
       , sList = []
259 fd7a7c73 Iustin Pop
       , failN1 = True
260 fd7a7c73 Iustin Pop
       , idx = -1
261 fd7a7c73 Iustin Pop
       , peers = P.empty
262 fd7a7c73 Iustin Pop
       , rMem = 0
263 fd7a7c73 Iustin Pop
       , pMem = fromIntegral mem_f_init / mem_t_init
264 825f8cee Bernardo Dal Seno
       , pDsk = if excl_stor
265 825f8cee Bernardo Dal Seno
                then computePDsk spindles_f_init $ fromIntegral spindles_t_init
266 825f8cee Bernardo Dal Seno
                else computePDsk dsk_f_init dsk_t_init
267 fd7a7c73 Iustin Pop
       , pRem = 0
268 c8c071cb Bernardo Dal Seno
       , pCpu = fromIntegral cpu_n_init / cpu_t_init
269 fd7a7c73 Iustin Pop
       , offline = offline_init
270 6c332a37 Klaus Aehlig
       , isMaster = False
271 07ea9bf5 Klaus Aehlig
       , nTags = []
272 fd7a7c73 Iustin Pop
       , xMem = 0
273 fd7a7c73 Iustin Pop
       , mDsk = T.defReservedDiskRatio
274 fd7a7c73 Iustin Pop
       , loDsk = mDskToloDsk T.defReservedDiskRatio dsk_t_init
275 487e1962 Iustin Pop
       , hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio T.defIPolicy) cpu_t_init
276 8bc34c7b Iustin Pop
       , hiSpindles = computeHiSpindles (T.iPolicySpindleRatio T.defIPolicy)
277 96f9b0a6 Bernardo Dal Seno
                      spindles_t_init
278 8bc34c7b Iustin Pop
       , instSpindles = 0
279 fd7a7c73 Iustin Pop
       , utilPool = T.baseUtil
280 fd7a7c73 Iustin Pop
       , utilLoad = T.zeroUtil
281 fd7a7c73 Iustin Pop
       , pTags = Map.empty
282 fd7a7c73 Iustin Pop
       , group = group_init
283 d6eec019 Iustin Pop
       , iPolicy = T.defIPolicy
284 c324da14 Bernardo Dal Seno
       , exclStorage = excl_stor
285 fd7a7c73 Iustin Pop
       }
286 e4f08c46 Iustin Pop
287 525bfb36 Iustin Pop
-- | Conversion formula from mDsk\/tDsk to loDsk.
288 f4c0b8c5 Iustin Pop
mDskToloDsk :: Double -> Double -> Int
289 05ff7a00 Agata Murawska
mDskToloDsk mval = floor . (mval *)
290 f4c0b8c5 Iustin Pop
291 525bfb36 Iustin Pop
-- | Conversion formula from mCpu\/tCpu to hiCpu.
292 f4c0b8c5 Iustin Pop
mCpuTohiCpu :: Double -> Double -> Int
293 05ff7a00 Agata Murawska
mCpuTohiCpu mval = floor . (mval *)
294 f4c0b8c5 Iustin Pop
295 8bc34c7b Iustin Pop
-- | Conversiojn formula from spindles and spindle ratio to hiSpindles.
296 8bc34c7b Iustin Pop
computeHiSpindles :: Double -> Int -> Double
297 8bc34c7b Iustin Pop
computeHiSpindles spindle_ratio = (spindle_ratio *) . fromIntegral
298 8bc34c7b Iustin Pop
299 e4f08c46 Iustin Pop
-- | Changes the index.
300 9188aeef Iustin Pop
--
301 e4f08c46 Iustin Pop
-- This is used only during the building of the data structures.
302 608efcce Iustin Pop
setIdx :: Node -> T.Ndx -> Node
303 e4f08c46 Iustin Pop
setIdx t i = t {idx = i}
304 e4f08c46 Iustin Pop
305 8bcdde0c Iustin Pop
-- | Changes the alias.
306 8bcdde0c Iustin Pop
--
307 8bcdde0c Iustin Pop
-- This is used only during the building of the data structures.
308 8bcdde0c Iustin Pop
setAlias :: Node -> String -> Node
309 8bcdde0c Iustin Pop
setAlias t s = t { alias = s }
310 497e30a1 Iustin Pop
311 9188aeef Iustin Pop
-- | Sets the offline attribute.
312 c2c1ef0c Iustin Pop
setOffline :: Node -> Bool -> Node
313 c2c1ef0c Iustin Pop
setOffline t val = t { offline = val }
314 c2c1ef0c Iustin Pop
315 6c332a37 Klaus Aehlig
-- | Sets the master attribute
316 6c332a37 Klaus Aehlig
setMaster :: Node -> Bool -> Node
317 6c332a37 Klaus Aehlig
setMaster t val = t { isMaster = val }
318 6c332a37 Klaus Aehlig
319 07ea9bf5 Klaus Aehlig
-- | Sets the node tags attribute
320 07ea9bf5 Klaus Aehlig
setNodeTags :: Node -> [String] -> Node
321 07ea9bf5 Klaus Aehlig
setNodeTags t val = t { nTags = val }
322 07ea9bf5 Klaus Aehlig
323 9188aeef Iustin Pop
-- | Sets the unnaccounted memory.
324 8c5b0a0d Iustin Pop
setXmem :: Node -> Int -> Node
325 2060348b Iustin Pop
setXmem t val = t { xMem = val }
326 8c5b0a0d Iustin Pop
327 525bfb36 Iustin Pop
-- | Sets the max disk usage ratio.
328 844eff86 Iustin Pop
setMdsk :: Node -> Double -> Node
329 f4c0b8c5 Iustin Pop
setMdsk t val = t { mDsk = val, loDsk = mDskToloDsk val (tDsk t) }
330 844eff86 Iustin Pop
331 487e1962 Iustin Pop
-- | Sets the max cpu usage ratio. This will update the node's
332 487e1962 Iustin Pop
-- ipolicy, losing sharing (but it should be a seldomly done operation).
333 844eff86 Iustin Pop
setMcpu :: Node -> Double -> Node
334 487e1962 Iustin Pop
setMcpu t val =
335 487e1962 Iustin Pop
  let new_ipol = (iPolicy t) { T.iPolicyVcpuRatio = val }
336 487e1962 Iustin Pop
  in t { hiCpu = mCpuTohiCpu val (tCpu t), iPolicy = new_ipol }
337 844eff86 Iustin Pop
338 d6eec019 Iustin Pop
-- | Sets the policy.
339 d6eec019 Iustin Pop
setPolicy :: T.IPolicy -> Node -> Node
340 487e1962 Iustin Pop
setPolicy pol node =
341 487e1962 Iustin Pop
  node { iPolicy = pol
342 8bc34c7b Iustin Pop
       , hiCpu = mCpuTohiCpu (T.iPolicyVcpuRatio pol) (tCpu node)
343 8bc34c7b Iustin Pop
       , hiSpindles = computeHiSpindles (T.iPolicySpindleRatio pol)
344 96f9b0a6 Bernardo Dal Seno
                      (tSpindles node)
345 8bc34c7b Iustin Pop
       }
346 d6eec019 Iustin Pop
347 e4f08c46 Iustin Pop
-- | Computes the maximum reserved memory for peers from a peer map.
348 12e6776a Iustin Pop
computeMaxRes :: P.PeerMap -> P.Elem
349 12e6776a Iustin Pop
computeMaxRes = P.maxElem
350 e4f08c46 Iustin Pop
351 e4f08c46 Iustin Pop
-- | Builds the peer map for a given node.
352 9cf4267a Iustin Pop
buildPeers :: Node -> Instance.List -> Node
353 9cf4267a Iustin Pop
buildPeers t il =
354 fd7a7c73 Iustin Pop
  let mdata = map
355 fd7a7c73 Iustin Pop
              (\i_idx -> let inst = Container.find i_idx il
356 55bd1414 Iustin Pop
                             mem = if Instance.usesSecMem inst
357 929b60d8 Iustin Pop
                                     then Instance.mem inst
358 929b60d8 Iustin Pop
                                     else 0
359 fd7a7c73 Iustin Pop
                         in (Instance.pNode inst, mem))
360 fd7a7c73 Iustin Pop
              (sList t)
361 fd7a7c73 Iustin Pop
      pmap = P.accumArray (+) mdata
362 fd7a7c73 Iustin Pop
      new_rmem = computeMaxRes pmap
363 fd7a7c73 Iustin Pop
      new_failN1 = fMem t <= new_rmem
364 fd7a7c73 Iustin Pop
      new_prem = fromIntegral new_rmem / tMem t
365 fd7a7c73 Iustin Pop
  in t {peers=pmap, failN1 = new_failN1, rMem = new_rmem, pRem = new_prem}
366 e4f08c46 Iustin Pop
367 4c18f468 Renรฉ Nussbaumer
-- | Calculate the new spindle usage
368 74ff6aed Bernardo Dal Seno
calcSpindleUse ::
369 74ff6aed Bernardo Dal Seno
                  Bool -- Action: True = adding instance, False = removing it
370 74ff6aed Bernardo Dal Seno
               -> Node -> Instance.Instance -> Double
371 74ff6aed Bernardo Dal Seno
calcSpindleUse _ (Node {exclStorage = True}) _ = 0.0
372 74ff6aed Bernardo Dal Seno
calcSpindleUse act n@(Node {exclStorage = False}) i =
373 74ff6aed Bernardo Dal Seno
  f (Instance.usesLocalStorage i) (instSpindles n)
374 74ff6aed Bernardo Dal Seno
    (fromIntegral $ Instance.spindleUse i)
375 74ff6aed Bernardo Dal Seno
    where
376 74ff6aed Bernardo Dal Seno
      f :: Bool -> Double -> Double -> Double -- avoid monomorphism restriction
377 74ff6aed Bernardo Dal Seno
      f = if act then incIf else decIf
378 74ff6aed Bernardo Dal Seno
379 74ff6aed Bernardo Dal Seno
-- | Calculate the new number of free spindles
380 74ff6aed Bernardo Dal Seno
calcNewFreeSpindles ::
381 74ff6aed Bernardo Dal Seno
                       Bool -- Action: True = adding instance, False = removing
382 74ff6aed Bernardo Dal Seno
                    -> Node -> Instance.Instance -> Int
383 74ff6aed Bernardo Dal Seno
calcNewFreeSpindles _ (Node {exclStorage = False}) _ = 0
384 74ff6aed Bernardo Dal Seno
calcNewFreeSpindles act n@(Node {exclStorage = True}) i =
385 74ff6aed Bernardo Dal Seno
  case Instance.getTotalSpindles i of
386 74ff6aed Bernardo Dal Seno
    Nothing -> if act
387 74ff6aed Bernardo Dal Seno
               then -1 -- Force a spindle error, so the instance don't go here
388 74ff6aed Bernardo Dal Seno
               else fSpindles n -- No change, as we aren't sure
389 74ff6aed Bernardo Dal Seno
    Just s -> (if act then (-) else (+)) (fSpindles n) s
390 4c18f468 Renรฉ Nussbaumer
391 a488a217 Iustin Pop
-- | Assigns an instance to a node as primary and update the used VCPU
392 5f0b9579 Iustin Pop
-- count, utilisation data and tags map.
393 a488a217 Iustin Pop
setPri :: Node -> Instance.Instance -> Node
394 aa8d2e71 Iustin Pop
setPri t inst = t { pList = Instance.idx inst:pList t
395 a488a217 Iustin Pop
                  , uCpu = new_count
396 aa8d2e71 Iustin Pop
                  , pCpu = fromIntegral new_count / tCpu t
397 aa8d2e71 Iustin Pop
                  , utilLoad = utilLoad t `T.addUtil` Instance.util inst
398 2f907bad Dato Simรณ
                  , pTags = addTags (pTags t) (Instance.exclTags inst)
399 74ff6aed Bernardo Dal Seno
                  , instSpindles = calcSpindleUse True t inst
400 aa8d2e71 Iustin Pop
                  }
401 55bd1414 Iustin Pop
  where new_count = Instance.applyIfOnline inst (+ Instance.vcpus inst)
402 55bd1414 Iustin Pop
                    (uCpu t )
403 9188aeef Iustin Pop
404 74ff6aed Bernardo Dal Seno
-- | Assigns an instance to a node as secondary and updates disk utilisation.
405 a488a217 Iustin Pop
setSec :: Node -> Instance.Instance -> Node
406 aa8d2e71 Iustin Pop
setSec t inst = t { sList = Instance.idx inst:sList t
407 aa8d2e71 Iustin Pop
                  , utilLoad = old_load { T.dskWeight = T.dskWeight old_load +
408 aa8d2e71 Iustin Pop
                                          T.dskWeight (Instance.util inst) }
409 74ff6aed Bernardo Dal Seno
                  , instSpindles = calcSpindleUse True t inst
410 aa8d2e71 Iustin Pop
                  }
411 fd7a7c73 Iustin Pop
  where old_load = utilLoad t
412 1a82215d Iustin Pop
413 b7743258 Iustin Pop
-- | Computes the new 'pDsk' value, handling nodes without local disk
414 825f8cee Bernardo Dal Seno
-- storage (we consider all their disk unused).
415 b7743258 Iustin Pop
computePDsk :: Int -> Double -> Double
416 b7743258 Iustin Pop
computePDsk _    0     = 1
417 825f8cee Bernardo Dal Seno
computePDsk free total = fromIntegral free / total
418 825f8cee Bernardo Dal Seno
419 825f8cee Bernardo Dal Seno
-- | Computes the new 'pDsk' value, handling the exclusive storage state.
420 825f8cee Bernardo Dal Seno
computeNewPDsk :: Node -> Int -> Int -> Double
421 825f8cee Bernardo Dal Seno
computeNewPDsk node new_free_sp new_free_dsk =
422 825f8cee Bernardo Dal Seno
  if exclStorage node
423 825f8cee Bernardo Dal Seno
  then computePDsk new_free_sp . fromIntegral $ tSpindles node
424 825f8cee Bernardo Dal Seno
  else computePDsk new_free_dsk $ tDsk node
425 b7743258 Iustin Pop
426 9188aeef Iustin Pop
-- * Update functions
427 9188aeef Iustin Pop
428 9188aeef Iustin Pop
-- | Sets the free memory.
429 9188aeef Iustin Pop
setFmem :: Node -> Int -> Node
430 9188aeef Iustin Pop
setFmem t new_mem =
431 77ffd663 Helga Velroyen
  let new_n1 = new_mem < rMem t
432 fd7a7c73 Iustin Pop
      new_mp = fromIntegral new_mem / tMem t
433 fd7a7c73 Iustin Pop
  in t { fMem = new_mem, failN1 = new_n1, pMem = new_mp }
434 9188aeef Iustin Pop
435 e4f08c46 Iustin Pop
-- | Removes a primary instance.
436 e4f08c46 Iustin Pop
removePri :: Node -> Instance.Instance -> Node
437 e4f08c46 Iustin Pop
removePri t inst =
438 fd7a7c73 Iustin Pop
  let iname = Instance.idx inst
439 7959cbb9 Iustin Pop
      i_online = Instance.notOffline inst
440 f87c9f5d Iustin Pop
      uses_disk = Instance.usesLocalStorage inst
441 fd7a7c73 Iustin Pop
      new_plist = delete iname (pList t)
442 f87c9f5d Iustin Pop
      new_mem = incIf i_online (fMem t) (Instance.mem inst)
443 f87c9f5d Iustin Pop
      new_dsk = incIf uses_disk (fDsk t) (Instance.dsk inst)
444 74ff6aed Bernardo Dal Seno
      new_free_sp = calcNewFreeSpindles False t inst
445 74ff6aed Bernardo Dal Seno
      new_inst_sp = calcSpindleUse False t inst
446 fd7a7c73 Iustin Pop
      new_mp = fromIntegral new_mem / tMem t
447 825f8cee Bernardo Dal Seno
      new_dp = computeNewPDsk t new_free_sp new_dsk
448 fd7a7c73 Iustin Pop
      new_failn1 = new_mem <= rMem t
449 f87c9f5d Iustin Pop
      new_ucpu = decIf i_online (uCpu t) (Instance.vcpus inst)
450 fd7a7c73 Iustin Pop
      new_rcpu = fromIntegral new_ucpu / tCpu t
451 fd7a7c73 Iustin Pop
      new_load = utilLoad t `T.subUtil` Instance.util inst
452 fd7a7c73 Iustin Pop
  in t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
453 fd7a7c73 Iustin Pop
       , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
454 fd7a7c73 Iustin Pop
       , uCpu = new_ucpu, pCpu = new_rcpu, utilLoad = new_load
455 2f907bad Dato Simรณ
       , pTags = delTags (pTags t) (Instance.exclTags inst)
456 74ff6aed Bernardo Dal Seno
       , instSpindles = new_inst_sp, fSpindles = new_free_sp
457 82f19570 Iustin Pop
       }
458 e4f08c46 Iustin Pop
459 e4f08c46 Iustin Pop
-- | Removes a secondary instance.
460 e4f08c46 Iustin Pop
removeSec :: Node -> Instance.Instance -> Node
461 e4f08c46 Iustin Pop
removeSec t inst =
462 fd7a7c73 Iustin Pop
  let iname = Instance.idx inst
463 f87c9f5d Iustin Pop
      uses_disk = Instance.usesLocalStorage inst
464 fd7a7c73 Iustin Pop
      cur_dsk = fDsk t
465 fd7a7c73 Iustin Pop
      pnode = Instance.pNode inst
466 fd7a7c73 Iustin Pop
      new_slist = delete iname (sList t)
467 f87c9f5d Iustin Pop
      new_dsk = incIf uses_disk cur_dsk (Instance.dsk inst)
468 74ff6aed Bernardo Dal Seno
      new_free_sp = calcNewFreeSpindles False t inst
469 74ff6aed Bernardo Dal Seno
      new_inst_sp = calcSpindleUse False t inst
470 fd7a7c73 Iustin Pop
      old_peers = peers t
471 fd7a7c73 Iustin Pop
      old_peem = P.find pnode old_peers
472 f87c9f5d Iustin Pop
      new_peem = decIf (Instance.usesSecMem inst) old_peem (Instance.mem inst)
473 fd7a7c73 Iustin Pop
      new_peers = if new_peem > 0
474 124b7cd7 Iustin Pop
                    then P.add pnode new_peem old_peers
475 124b7cd7 Iustin Pop
                    else P.remove pnode old_peers
476 fd7a7c73 Iustin Pop
      old_rmem = rMem t
477 fd7a7c73 Iustin Pop
      new_rmem = if old_peem < old_rmem
478 bbd8efd2 Iustin Pop
                   then old_rmem
479 bbd8efd2 Iustin Pop
                   else computeMaxRes new_peers
480 fd7a7c73 Iustin Pop
      new_prem = fromIntegral new_rmem / tMem t
481 fd7a7c73 Iustin Pop
      new_failn1 = fMem t <= new_rmem
482 825f8cee Bernardo Dal Seno
      new_dp = computeNewPDsk t new_free_sp new_dsk
483 fd7a7c73 Iustin Pop
      old_load = utilLoad t
484 fd7a7c73 Iustin Pop
      new_load = old_load { T.dskWeight = T.dskWeight old_load -
485 fd7a7c73 Iustin Pop
                                          T.dskWeight (Instance.util inst) }
486 fd7a7c73 Iustin Pop
  in t { sList = new_slist, fDsk = new_dsk, peers = new_peers
487 fd7a7c73 Iustin Pop
       , failN1 = new_failn1, rMem = new_rmem, pDsk = new_dp
488 82f19570 Iustin Pop
       , pRem = new_prem, utilLoad = new_load
489 74ff6aed Bernardo Dal Seno
       , instSpindles = new_inst_sp, fSpindles = new_free_sp
490 82f19570 Iustin Pop
       }
491 e4f08c46 Iustin Pop
492 3e3c9393 Iustin Pop
-- | Adds a primary instance (basic version).
493 f2280553 Iustin Pop
addPri :: Node -> Instance.Instance -> T.OpResult Node
494 3e3c9393 Iustin Pop
addPri = addPriEx False
495 3e3c9393 Iustin Pop
496 3e3c9393 Iustin Pop
-- | Adds a primary instance (extended version).
497 3e3c9393 Iustin Pop
addPriEx :: Bool               -- ^ Whether to override the N+1 and
498 3e3c9393 Iustin Pop
                               -- other /soft/ checks, useful if we
499 3e3c9393 Iustin Pop
                               -- come from a worse status
500 3e3c9393 Iustin Pop
                               -- (e.g. offline)
501 3e3c9393 Iustin Pop
         -> Node               -- ^ The target node
502 3e3c9393 Iustin Pop
         -> Instance.Instance  -- ^ The instance to add
503 3e3c9393 Iustin Pop
         -> T.OpResult Node    -- ^ The result of the operation,
504 3e3c9393 Iustin Pop
                               -- either the new version of the node
505 3e3c9393 Iustin Pop
                               -- or a failure mode
506 3e3c9393 Iustin Pop
addPriEx force t inst =
507 fd7a7c73 Iustin Pop
  let iname = Instance.idx inst
508 7959cbb9 Iustin Pop
      i_online = Instance.notOffline inst
509 fd7a7c73 Iustin Pop
      uses_disk = Instance.usesLocalStorage inst
510 fd7a7c73 Iustin Pop
      cur_dsk = fDsk t
511 f87c9f5d Iustin Pop
      new_mem = decIf i_online (fMem t) (Instance.mem inst)
512 f87c9f5d Iustin Pop
      new_dsk = decIf uses_disk cur_dsk (Instance.dsk inst)
513 74ff6aed Bernardo Dal Seno
      new_free_sp = calcNewFreeSpindles True t inst
514 74ff6aed Bernardo Dal Seno
      new_inst_sp = calcSpindleUse True t inst
515 fd7a7c73 Iustin Pop
      new_failn1 = new_mem <= rMem t
516 f87c9f5d Iustin Pop
      new_ucpu = incIf i_online (uCpu t) (Instance.vcpus inst)
517 fd7a7c73 Iustin Pop
      new_pcpu = fromIntegral new_ucpu / tCpu t
518 825f8cee Bernardo Dal Seno
      new_dp = computeNewPDsk t new_free_sp new_dsk
519 487e1962 Iustin Pop
      l_cpu = T.iPolicyVcpuRatio $ iPolicy t
520 fd7a7c73 Iustin Pop
      new_load = utilLoad t `T.addUtil` Instance.util inst
521 2f907bad Dato Simรณ
      inst_tags = Instance.exclTags inst
522 fd7a7c73 Iustin Pop
      old_tags = pTags t
523 fd7a7c73 Iustin Pop
      strict = not force
524 fd7a7c73 Iustin Pop
  in case () of
525 a8038349 Iustin Pop
       _ | new_mem <= 0 -> Bad T.FailMem
526 a8038349 Iustin Pop
         | uses_disk && new_dsk <= 0 -> Bad T.FailDisk
527 825f8cee Bernardo Dal Seno
         | uses_disk && new_dsk < loDsk t && strict -> Bad T.FailDisk
528 74ff6aed Bernardo Dal Seno
         | uses_disk && exclStorage t && new_free_sp < 0 -> Bad T.FailSpindles
529 74ff6aed Bernardo Dal Seno
         | uses_disk && new_inst_sp > hiSpindles t && strict -> Bad T.FailDisk
530 a8038349 Iustin Pop
         | new_failn1 && not (failN1 t) && strict -> Bad T.FailMem
531 a8038349 Iustin Pop
         | l_cpu >= 0 && l_cpu < new_pcpu && strict -> Bad T.FailCPU
532 a8038349 Iustin Pop
         | rejectAddTags old_tags inst_tags -> Bad T.FailTags
533 fd7a7c73 Iustin Pop
         | otherwise ->
534 fd7a7c73 Iustin Pop
           let new_plist = iname:pList t
535 fd7a7c73 Iustin Pop
               new_mp = fromIntegral new_mem / tMem t
536 fd7a7c73 Iustin Pop
               r = t { pList = new_plist, fMem = new_mem, fDsk = new_dsk
537 fd7a7c73 Iustin Pop
                     , failN1 = new_failn1, pMem = new_mp, pDsk = new_dp
538 fd7a7c73 Iustin Pop
                     , uCpu = new_ucpu, pCpu = new_pcpu
539 fd7a7c73 Iustin Pop
                     , utilLoad = new_load
540 82f19570 Iustin Pop
                     , pTags = addTags old_tags inst_tags
541 74ff6aed Bernardo Dal Seno
                     , instSpindles = new_inst_sp
542 74ff6aed Bernardo Dal Seno
                     , fSpindles = new_free_sp
543 82f19570 Iustin Pop
                     }
544 a8038349 Iustin Pop
           in Ok r
545 e4f08c46 Iustin Pop
546 3e3c9393 Iustin Pop
-- | Adds a secondary instance (basic version).
547 f2280553 Iustin Pop
addSec :: Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
548 3e3c9393 Iustin Pop
addSec = addSecEx False
549 3e3c9393 Iustin Pop
550 3e3c9393 Iustin Pop
-- | Adds a secondary instance (extended version).
551 3e3c9393 Iustin Pop
addSecEx :: Bool -> Node -> Instance.Instance -> T.Ndx -> T.OpResult Node
552 3e3c9393 Iustin Pop
addSecEx force t inst pdx =
553 fd7a7c73 Iustin Pop
  let iname = Instance.idx inst
554 fd7a7c73 Iustin Pop
      old_peers = peers t
555 fd7a7c73 Iustin Pop
      old_mem = fMem t
556 fd7a7c73 Iustin Pop
      new_dsk = fDsk t - Instance.dsk inst
557 74ff6aed Bernardo Dal Seno
      new_free_sp = calcNewFreeSpindles True t inst
558 74ff6aed Bernardo Dal Seno
      new_inst_sp = calcSpindleUse True t inst
559 55bd1414 Iustin Pop
      secondary_needed_mem = if Instance.usesSecMem inst
560 929b60d8 Iustin Pop
                               then Instance.mem inst
561 929b60d8 Iustin Pop
                               else 0
562 fd7a7c73 Iustin Pop
      new_peem = P.find pdx old_peers + secondary_needed_mem
563 fd7a7c73 Iustin Pop
      new_peers = P.add pdx new_peem old_peers
564 fd7a7c73 Iustin Pop
      new_rmem = max (rMem t) new_peem
565 fd7a7c73 Iustin Pop
      new_prem = fromIntegral new_rmem / tMem t
566 fd7a7c73 Iustin Pop
      new_failn1 = old_mem <= new_rmem
567 825f8cee Bernardo Dal Seno
      new_dp = computeNewPDsk t new_free_sp new_dsk
568 fd7a7c73 Iustin Pop
      old_load = utilLoad t
569 fd7a7c73 Iustin Pop
      new_load = old_load { T.dskWeight = T.dskWeight old_load +
570 fd7a7c73 Iustin Pop
                                          T.dskWeight (Instance.util inst) }
571 fd7a7c73 Iustin Pop
      strict = not force
572 fd7a7c73 Iustin Pop
  in case () of
573 a8038349 Iustin Pop
       _ | not (Instance.hasSecondary inst) -> Bad T.FailDisk
574 a8038349 Iustin Pop
         | new_dsk <= 0 -> Bad T.FailDisk
575 825f8cee Bernardo Dal Seno
         | new_dsk < loDsk t && strict -> Bad T.FailDisk
576 74ff6aed Bernardo Dal Seno
         | exclStorage t && new_free_sp < 0 -> Bad T.FailSpindles
577 74ff6aed Bernardo Dal Seno
         | new_inst_sp > hiSpindles t && strict -> Bad T.FailDisk
578 a8038349 Iustin Pop
         | secondary_needed_mem >= old_mem && strict -> Bad T.FailMem
579 a8038349 Iustin Pop
         | new_failn1 && not (failN1 t) && strict -> Bad T.FailMem
580 fd7a7c73 Iustin Pop
         | otherwise ->
581 fd7a7c73 Iustin Pop
           let new_slist = iname:sList t
582 fd7a7c73 Iustin Pop
               r = t { sList = new_slist, fDsk = new_dsk
583 fd7a7c73 Iustin Pop
                     , peers = new_peers, failN1 = new_failn1
584 fd7a7c73 Iustin Pop
                     , rMem = new_rmem, pDsk = new_dp
585 82f19570 Iustin Pop
                     , pRem = new_prem, utilLoad = new_load
586 74ff6aed Bernardo Dal Seno
                     , instSpindles = new_inst_sp
587 74ff6aed Bernardo Dal Seno
                     , fSpindles = new_free_sp
588 82f19570 Iustin Pop
                     }
589 a8038349 Iustin Pop
           in Ok r
590 e4f08c46 Iustin Pop
591 fe3d6f02 Iustin Pop
-- * Stats functions
592 fe3d6f02 Iustin Pop
593 525bfb36 Iustin Pop
-- | Computes the amount of available disk on a given node.
594 fe3d6f02 Iustin Pop
availDisk :: Node -> Int
595 fe3d6f02 Iustin Pop
availDisk t =
596 fd7a7c73 Iustin Pop
  let _f = fDsk t
597 fd7a7c73 Iustin Pop
      _l = loDsk t
598 fd7a7c73 Iustin Pop
  in if _f < _l
599 f4c0b8c5 Iustin Pop
       then 0
600 f4c0b8c5 Iustin Pop
       else _f - _l
601 fe3d6f02 Iustin Pop
602 525bfb36 Iustin Pop
-- | Computes the amount of used disk on a given node.
603 55da339e Iustin Pop
iDsk :: Node -> Int
604 55da339e Iustin Pop
iDsk t = truncate (tDsk t) - fDsk t
605 55da339e Iustin Pop
606 525bfb36 Iustin Pop
-- | Computes the amount of available memory on a given node.
607 1e3dccc8 Iustin Pop
availMem :: Node -> Int
608 1e3dccc8 Iustin Pop
availMem t =
609 fd7a7c73 Iustin Pop
  let _f = fMem t
610 fd7a7c73 Iustin Pop
      _l = rMem t
611 fd7a7c73 Iustin Pop
  in if _f < _l
612 1e3dccc8 Iustin Pop
       then 0
613 1e3dccc8 Iustin Pop
       else _f - _l
614 1e3dccc8 Iustin Pop
615 525bfb36 Iustin Pop
-- | Computes the amount of available memory on a given node.
616 1e3dccc8 Iustin Pop
availCpu :: Node -> Int
617 1e3dccc8 Iustin Pop
availCpu t =
618 fd7a7c73 Iustin Pop
  let _u = uCpu t
619 fd7a7c73 Iustin Pop
      _l = hiCpu t
620 fd7a7c73 Iustin Pop
  in if _l >= _u
621 1e3dccc8 Iustin Pop
       then _l - _u
622 1e3dccc8 Iustin Pop
       else 0
623 1e3dccc8 Iustin Pop
624 425af248 Iustin Pop
-- | The memory used by instances on a given node.
625 425af248 Iustin Pop
iMem :: Node -> Int
626 425af248 Iustin Pop
iMem t = truncate (tMem t) - nMem t - xMem t - fMem t
627 425af248 Iustin Pop
628 dae1f9cb Guido Trotter
-- * Node graph functions
629 dae1f9cb Guido Trotter
-- These functions do the transformations needed so that nodes can be
630 dae1f9cb Guido Trotter
-- represented as a graph connected by the instances that are replicated
631 dae1f9cb Guido Trotter
-- on them.
632 dae1f9cb Guido Trotter
633 dae1f9cb Guido Trotter
-- * Making of a Graph from a node/instance list
634 dae1f9cb Guido Trotter
635 dae1f9cb Guido Trotter
-- | Transform an instance into a list of edges on the node graph
636 dae1f9cb Guido Trotter
instanceToEdges :: Instance.Instance -> [Graph.Edge]
637 dae1f9cb Guido Trotter
instanceToEdges i
638 dae1f9cb Guido Trotter
  | Instance.hasSecondary i = [(pnode,snode), (snode,pnode)]
639 dae1f9cb Guido Trotter
  | otherwise = []
640 dae1f9cb Guido Trotter
    where pnode = Instance.pNode i
641 dae1f9cb Guido Trotter
          snode = Instance.sNode i
642 dae1f9cb Guido Trotter
643 dae1f9cb Guido Trotter
-- | Transform the list of instances into list of destination edges
644 dae1f9cb Guido Trotter
instancesToEdges :: Instance.List -> [Graph.Edge]
645 dae1f9cb Guido Trotter
instancesToEdges = concatMap instanceToEdges . Container.elems
646 dae1f9cb Guido Trotter
647 dae1f9cb Guido Trotter
-- | Transform the list of nodes into vertices bounds.
648 dae1f9cb Guido Trotter
-- Returns Nothing is the list is empty.
649 dae1f9cb Guido Trotter
nodesToBounds :: List -> Maybe Graph.Bounds
650 dae1f9cb Guido Trotter
nodesToBounds nl = liftM2 (,) nmin nmax
651 dae1f9cb Guido Trotter
    where nmin = fmap (fst . fst) (IntMap.minViewWithKey nl)
652 dae1f9cb Guido Trotter
          nmax = fmap (fst . fst) (IntMap.maxViewWithKey nl)
653 dae1f9cb Guido Trotter
654 30fded87 Klaus Aehlig
-- | The clique of the primary nodes of the instances with a given secondary.
655 30fded87 Klaus Aehlig
-- Return the full graph of those nodes that are primary node of at least one
656 30fded87 Klaus Aehlig
-- instance that has the given node as secondary.
657 30fded87 Klaus Aehlig
nodeToSharedSecondaryEdge :: Instance.List -> Node -> [Graph.Edge]
658 30fded87 Klaus Aehlig
nodeToSharedSecondaryEdge il n = (,) <$> primaries <*> primaries
659 30fded87 Klaus Aehlig
  where primaries = map (Instance.pNode . flip Container.find il) $ sList n
660 30fded87 Klaus Aehlig
661 30fded87 Klaus Aehlig
662 30fded87 Klaus Aehlig
-- | Predicate of an edge having both vertices in a set of nodes.
663 30fded87 Klaus Aehlig
filterValid :: List -> [Graph.Edge] -> [Graph.Edge]
664 30fded87 Klaus Aehlig
filterValid nl  =  filter $ \(x,y) -> IntMap.member x nl && IntMap.member y nl
665 30fded87 Klaus Aehlig
666 dae1f9cb Guido Trotter
-- | Transform a Node + Instance list into a NodeGraph type.
667 dae1f9cb Guido Trotter
-- Returns Nothing if the node list is empty.
668 dae1f9cb Guido Trotter
mkNodeGraph :: List -> Instance.List -> Maybe Graph.Graph
669 dae1f9cb Guido Trotter
mkNodeGraph nl il =
670 30fded87 Klaus Aehlig
  liftM (`Graph.buildG` (filterValid nl . instancesToEdges $ il))
671 318c0a6c Klaus Aehlig
  (nodesToBounds nl)
672 30fded87 Klaus Aehlig
673 30fded87 Klaus Aehlig
-- | Transform a Nodes + Instances into a NodeGraph with all reboot exclusions.
674 30fded87 Klaus Aehlig
-- This includes edges between nodes that are the primary nodes of instances
675 30fded87 Klaus Aehlig
-- that have the same secondary node. Nodes not in the node list will not be
676 30fded87 Klaus Aehlig
-- part of the graph, but they are still considered for the edges arising from
677 30fded87 Klaus Aehlig
-- two instances having the same secondary node.
678 30fded87 Klaus Aehlig
-- Return Nothing if the node list is empty.
679 30fded87 Klaus Aehlig
mkRebootNodeGraph :: List -> List -> Instance.List -> Maybe Graph.Graph
680 30fded87 Klaus Aehlig
mkRebootNodeGraph allnodes nl il =
681 30fded87 Klaus Aehlig
  liftM (`Graph.buildG` filterValid nl edges) (nodesToBounds nl)
682 318c0a6c Klaus Aehlig
  where
683 30fded87 Klaus Aehlig
    edges = instancesToEdges il `union`
684 30fded87 Klaus Aehlig
            (Container.elems allnodes >>= nodeToSharedSecondaryEdge il) 
685 dae1f9cb Guido Trotter
686 9188aeef Iustin Pop
-- * Display functions
687 01f6a5d2 Iustin Pop
688 525bfb36 Iustin Pop
-- | Return a field for a given node.
689 525bfb36 Iustin Pop
showField :: Node   -- ^ Node which we're querying
690 525bfb36 Iustin Pop
          -> String -- ^ Field name
691 525bfb36 Iustin Pop
          -> String -- ^ Field value as string
692 c5f7412e Iustin Pop
showField t field =
693 fd7a7c73 Iustin Pop
  case field of
694 fd7a7c73 Iustin Pop
    "idx"  -> printf "%4d" $ idx t
695 fd7a7c73 Iustin Pop
    "name" -> alias t
696 fd7a7c73 Iustin Pop
    "fqdn" -> name t
697 fd7a7c73 Iustin Pop
    "status" -> case () of
698 fd7a7c73 Iustin Pop
                  _ | offline t -> "-"
699 fd7a7c73 Iustin Pop
                    | failN1 t -> "*"
700 fd7a7c73 Iustin Pop
                    | otherwise -> " "
701 fd7a7c73 Iustin Pop
    "tmem" -> printf "%5.0f" $ tMem t
702 fd7a7c73 Iustin Pop
    "nmem" -> printf "%5d" $ nMem t
703 fd7a7c73 Iustin Pop
    "xmem" -> printf "%5d" $ xMem t
704 fd7a7c73 Iustin Pop
    "fmem" -> printf "%5d" $ fMem t
705 fd7a7c73 Iustin Pop
    "imem" -> printf "%5d" $ iMem t
706 fd7a7c73 Iustin Pop
    "rmem" -> printf "%5d" $ rMem t
707 fd7a7c73 Iustin Pop
    "amem" -> printf "%5d" $ fMem t - rMem t
708 fd7a7c73 Iustin Pop
    "tdsk" -> printf "%5.0f" $ tDsk t / 1024
709 fd7a7c73 Iustin Pop
    "fdsk" -> printf "%5d" $ fDsk t `div` 1024
710 fd7a7c73 Iustin Pop
    "tcpu" -> printf "%4.0f" $ tCpu t
711 fd7a7c73 Iustin Pop
    "ucpu" -> printf "%4d" $ uCpu t
712 fd7a7c73 Iustin Pop
    "pcnt" -> printf "%3d" $ length (pList t)
713 fd7a7c73 Iustin Pop
    "scnt" -> printf "%3d" $ length (sList t)
714 fd7a7c73 Iustin Pop
    "plist" -> show $ pList t
715 fd7a7c73 Iustin Pop
    "slist" -> show $ sList t
716 fd7a7c73 Iustin Pop
    "pfmem" -> printf "%6.4f" $ pMem t
717 fd7a7c73 Iustin Pop
    "pfdsk" -> printf "%6.4f" $ pDsk t
718 fd7a7c73 Iustin Pop
    "rcpu"  -> printf "%5.2f" $ pCpu t
719 fd7a7c73 Iustin Pop
    "cload" -> printf "%5.3f" uC
720 fd7a7c73 Iustin Pop
    "mload" -> printf "%5.3f" uM
721 fd7a7c73 Iustin Pop
    "dload" -> printf "%5.3f" uD
722 fd7a7c73 Iustin Pop
    "nload" -> printf "%5.3f" uN
723 fd7a7c73 Iustin Pop
    "ptags" -> intercalate "," . map (uncurry (printf "%s=%d")) .
724 fd7a7c73 Iustin Pop
               Map.toList $ pTags t
725 fd7a7c73 Iustin Pop
    "peermap" -> show $ peers t
726 96f9b0a6 Bernardo Dal Seno
    "spindle_count" -> show $ tSpindles t
727 34ace266 Iustin Pop
    "hi_spindles" -> show $ hiSpindles t
728 34ace266 Iustin Pop
    "inst_spindles" -> show $ instSpindles t
729 fd7a7c73 Iustin Pop
    _ -> T.unknownField
730 fd7a7c73 Iustin Pop
  where
731 fd7a7c73 Iustin Pop
    T.DynUtil { T.cpuWeight = uC, T.memWeight = uM,
732 fd7a7c73 Iustin Pop
                T.dskWeight = uD, T.netWeight = uN } = utilLoad t
733 c5f7412e Iustin Pop
734 525bfb36 Iustin Pop
-- | Returns the header and numeric propery of a field.
735 76354e11 Iustin Pop
showHeader :: String -> (String, Bool)
736 76354e11 Iustin Pop
showHeader field =
737 fd7a7c73 Iustin Pop
  case field of
738 fd7a7c73 Iustin Pop
    "idx" -> ("Index", True)
739 fd7a7c73 Iustin Pop
    "name" -> ("Name", False)
740 fd7a7c73 Iustin Pop
    "fqdn" -> ("Name", False)
741 fd7a7c73 Iustin Pop
    "status" -> ("F", False)
742 fd7a7c73 Iustin Pop
    "tmem" -> ("t_mem", True)
743 fd7a7c73 Iustin Pop
    "nmem" -> ("n_mem", True)
744 fd7a7c73 Iustin Pop
    "xmem" -> ("x_mem", True)
745 fd7a7c73 Iustin Pop
    "fmem" -> ("f_mem", True)
746 fd7a7c73 Iustin Pop
    "imem" -> ("i_mem", True)
747 fd7a7c73 Iustin Pop
    "rmem" -> ("r_mem", True)
748 fd7a7c73 Iustin Pop
    "amem" -> ("a_mem", True)
749 fd7a7c73 Iustin Pop
    "tdsk" -> ("t_dsk", True)
750 fd7a7c73 Iustin Pop
    "fdsk" -> ("f_dsk", True)
751 fd7a7c73 Iustin Pop
    "tcpu" -> ("pcpu", True)
752 fd7a7c73 Iustin Pop
    "ucpu" -> ("vcpu", True)
753 fd7a7c73 Iustin Pop
    "pcnt" -> ("pcnt", True)
754 fd7a7c73 Iustin Pop
    "scnt" -> ("scnt", True)
755 fd7a7c73 Iustin Pop
    "plist" -> ("primaries", True)
756 fd7a7c73 Iustin Pop
    "slist" -> ("secondaries", True)
757 fd7a7c73 Iustin Pop
    "pfmem" -> ("p_fmem", True)
758 fd7a7c73 Iustin Pop
    "pfdsk" -> ("p_fdsk", True)
759 fd7a7c73 Iustin Pop
    "rcpu"  -> ("r_cpu", True)
760 fd7a7c73 Iustin Pop
    "cload" -> ("lCpu", True)
761 fd7a7c73 Iustin Pop
    "mload" -> ("lMem", True)
762 fd7a7c73 Iustin Pop
    "dload" -> ("lDsk", True)
763 fd7a7c73 Iustin Pop
    "nload" -> ("lNet", True)
764 fd7a7c73 Iustin Pop
    "ptags" -> ("PrimaryTags", False)
765 fd7a7c73 Iustin Pop
    "peermap" -> ("PeerMap", False)
766 34ace266 Iustin Pop
    "spindle_count" -> ("NodeSpindles", True)
767 34ace266 Iustin Pop
    "hi_spindles" -> ("MaxSpindles", True)
768 34ace266 Iustin Pop
    "inst_spindles" -> ("InstSpindles", True)
769 fd7a7c73 Iustin Pop
    -- TODO: add node fields (group.uuid, group)
770 fd7a7c73 Iustin Pop
    _ -> (T.unknownField, False)
771 c5f7412e Iustin Pop
772 e4f08c46 Iustin Pop
-- | String converter for the node list functionality.
773 76354e11 Iustin Pop
list :: [String] -> Node -> [String]
774 76354e11 Iustin Pop
list fields t = map (showField t) fields
775 76354e11 Iustin Pop
776 525bfb36 Iustin Pop
-- | Constant holding the fields we're displaying by default.
777 76354e11 Iustin Pop
defaultFields :: [String]
778 76354e11 Iustin Pop
defaultFields =
779 fd7a7c73 Iustin Pop
  [ "status", "name", "tmem", "nmem", "imem", "xmem", "fmem"
780 fd7a7c73 Iustin Pop
  , "rmem", "tdsk", "fdsk", "tcpu", "ucpu", "pcnt", "scnt"
781 fd7a7c73 Iustin Pop
  , "pfmem", "pfdsk", "rcpu"
782 fd7a7c73 Iustin Pop
  , "cload", "mload", "dload", "nload" ]
783 d8bcd0a8 Iustin Pop
784 72747d91 Iustin Pop
{-# ANN computeGroups "HLint: ignore Use alternative" #-}
785 d8bcd0a8 Iustin Pop
-- | Split a list of nodes into a list of (node group UUID, list of
786 525bfb36 Iustin Pop
-- associated nodes).
787 10ef6b4e Iustin Pop
computeGroups :: [Node] -> [(T.Gdx, [Node])]
788 d8bcd0a8 Iustin Pop
computeGroups nodes =
789 d8bcd0a8 Iustin Pop
  let nodes' = sortBy (comparing group) nodes
790 86aa9ba3 Iustin Pop
      nodes'' = groupBy ((==) `on` group) nodes'
791 72747d91 Iustin Pop
  -- use of head here is OK, since groupBy returns non-empty lists; if
792 72747d91 Iustin Pop
  -- you remove groupBy, also remove use of head
793 d8bcd0a8 Iustin Pop
  in map (\nl -> (group (head nl), nl)) nodes''