Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Node.hs @ 29a30533

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