Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Node.hs @ 74ff6aed

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