Statistics
| Branch: | Tag: | Revision:

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

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