Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Node.hs @ 2207220d

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