Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / Node.hs @ 7959cbb9

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