Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Node.hs @ 09ab9fb2

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