Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Node.hs @ 7ec2f76b

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