Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hroller.hs @ 9d049fb4

History | View | Annotate | Download (17.7 kB)

1 3504d6c8 Guido Trotter
{-| Cluster rolling maintenance helper.
2 3504d6c8 Guido Trotter
3 3504d6c8 Guido Trotter
-}
4 3504d6c8 Guido Trotter
5 3504d6c8 Guido Trotter
{-
6 3504d6c8 Guido Trotter
7 3504d6c8 Guido Trotter
Copyright (C) 2012 Google Inc.
8 3504d6c8 Guido Trotter
9 3504d6c8 Guido Trotter
This program is free software; you can redistribute it and/or modify
10 3504d6c8 Guido Trotter
it under the terms of the GNU General Public License as published by
11 3504d6c8 Guido Trotter
the Free Software Foundation; either version 2 of the License, or
12 3504d6c8 Guido Trotter
(at your option) any later version.
13 3504d6c8 Guido Trotter
14 3504d6c8 Guido Trotter
This program is distributed in the hope that it will be useful, but
15 3504d6c8 Guido Trotter
WITHOUT ANY WARRANTY; without even the implied warranty of
16 3504d6c8 Guido Trotter
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 3504d6c8 Guido Trotter
General Public License for more details.
18 3504d6c8 Guido Trotter
19 3504d6c8 Guido Trotter
You should have received a copy of the GNU General Public License
20 3504d6c8 Guido Trotter
along with this program; if not, write to the Free Software
21 3504d6c8 Guido Trotter
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 3504d6c8 Guido Trotter
02110-1301, USA.
23 3504d6c8 Guido Trotter
24 3504d6c8 Guido Trotter
-}
25 3504d6c8 Guido Trotter
26 3504d6c8 Guido Trotter
module Ganeti.HTools.Program.Hroller
27 3504d6c8 Guido Trotter
  ( main
28 3504d6c8 Guido Trotter
  , options
29 3504d6c8 Guido Trotter
  , arguments
30 3504d6c8 Guido Trotter
  ) where
31 3504d6c8 Guido Trotter
32 442d5aae Klaus Aehlig
import Control.Applicative
33 30ce253e Klaus Aehlig
import Control.Arrow
34 1a9eb17e Guido Trotter
import Control.Monad
35 a39779f6 Klaus Aehlig
import Data.Function
36 1a9eb17e Guido Trotter
import Data.List
37 1a9eb17e Guido Trotter
import Data.Ord
38 30ce253e Klaus Aehlig
import Text.Printf
39 1a9eb17e Guido Trotter
40 1a9eb17e Guido Trotter
import qualified Data.IntMap as IntMap
41 1a9eb17e Guido Trotter
42 1a9eb17e Guido Trotter
import qualified Ganeti.HTools.Container as Container
43 1a9eb17e Guido Trotter
import qualified Ganeti.HTools.Node as Node
44 86c346db Klaus Aehlig
import qualified Ganeti.HTools.Instance as Instance
45 2fce67b6 Guido Trotter
import qualified Ganeti.HTools.Group as Group
46 1a9eb17e Guido Trotter
47 86c346db Klaus Aehlig
import Ganeti.BasicTypes
48 3504d6c8 Guido Trotter
import Ganeti.Common
49 3504d6c8 Guido Trotter
import Ganeti.HTools.CLI
50 1a9eb17e Guido Trotter
import Ganeti.HTools.ExtLoader
51 1a9eb17e Guido Trotter
import Ganeti.HTools.Graph
52 1a9eb17e Guido Trotter
import Ganeti.HTools.Loader
53 86c346db Klaus Aehlig
import Ganeti.HTools.Types
54 1a9eb17e Guido Trotter
import Ganeti.Utils
55 3504d6c8 Guido Trotter
56 3504d6c8 Guido Trotter
-- | Options list and functions.
57 3504d6c8 Guido Trotter
options :: IO [OptType]
58 3504d6c8 Guido Trotter
options = do
59 3504d6c8 Guido Trotter
  luxi <- oLuxiSocket
60 3504d6c8 Guido Trotter
  return
61 3504d6c8 Guido Trotter
    [ luxi
62 3504d6c8 Guido Trotter
    , oRapiMaster
63 3504d6c8 Guido Trotter
    , oDataFile
64 3504d6c8 Guido Trotter
    , oIAllocSrc
65 3504d6c8 Guido Trotter
    , oOfflineNode
66 8d38fb72 Klaus Aehlig
    , oOfflineMaintenance
67 3504d6c8 Guido Trotter
    , oVerbose
68 3504d6c8 Guido Trotter
    , oQuiet
69 3504d6c8 Guido Trotter
    , oNoHeaders
70 313fdabc Klaus Aehlig
    , oNodeTags
71 3504d6c8 Guido Trotter
    , oSaveCluster
72 2fce67b6 Guido Trotter
    , oGroup
73 30ce253e Klaus Aehlig
    , oPrintMoves
74 a12b230c Klaus Aehlig
    , oFullEvacuation
75 89363f98 Klaus Aehlig
    , oSkipNonRedundant
76 23247a73 Klaus Aehlig
    , oIgnoreNonRedundant
77 7dbe4c72 Klaus Aehlig
    , oForce
78 2207220d Klaus Aehlig
    , oOneStepOnly
79 3504d6c8 Guido Trotter
    ]
80 3504d6c8 Guido Trotter
81 3504d6c8 Guido Trotter
-- | The list of arguments supported by the program.
82 3504d6c8 Guido Trotter
arguments :: [ArgCompletion]
83 3504d6c8 Guido Trotter
arguments = []
84 3504d6c8 Guido Trotter
85 86c346db Klaus Aehlig
-- | Compute the result of moving an instance to a different node.
86 86c346db Klaus Aehlig
move :: Idx -> Ndx -> (Node.List, Instance.List)
87 86c346db Klaus Aehlig
        -> OpResult (Node.List, Instance.List)
88 86c346db Klaus Aehlig
move idx new_ndx (nl, il) = do
89 86c346db Klaus Aehlig
  let new_node = Container.find new_ndx nl
90 86c346db Klaus Aehlig
      inst = Container.find idx il
91 86c346db Klaus Aehlig
      old_ndx = Instance.pNode inst
92 86c346db Klaus Aehlig
      old_node = Container.find old_ndx nl
93 86c346db Klaus Aehlig
  new_node' <- Node.addPriEx True new_node inst
94 86c346db Klaus Aehlig
  let old_node' = Node.removePri old_node inst
95 86c346db Klaus Aehlig
      inst' = Instance.setPri inst new_ndx
96 86c346db Klaus Aehlig
      nl' = Container.addTwo old_ndx old_node' new_ndx new_node' nl
97 86c346db Klaus Aehlig
      il' = Container.add idx inst' il
98 86c346db Klaus Aehlig
  return (nl', il')
99 86c346db Klaus Aehlig
100 a8cbe1d7 Klaus Aehlig
-- | Move a non-redundant instance to one of the candidate nodes mentioned.
101 86c346db Klaus Aehlig
locateInstance :: Idx -> [Ndx] -> (Node.List, Instance.List)
102 86c346db Klaus Aehlig
                  -> Result (Node.List, Instance.List)
103 86c346db Klaus Aehlig
locateInstance idx ndxs conf =
104 86c346db Klaus Aehlig
  msum $ map (opToResult . flip (move idx) conf) ndxs
105 86c346db Klaus Aehlig
106 a8cbe1d7 Klaus Aehlig
-- | Move a list of non-redundant instances to some of the nodes mentioned.
107 86c346db Klaus Aehlig
locateInstances :: [Idx] -> [Ndx] -> (Node.List, Instance.List)
108 86c346db Klaus Aehlig
                   -> Result (Node.List, Instance.List)
109 86c346db Klaus Aehlig
locateInstances idxs ndxs conf =
110 86c346db Klaus Aehlig
  foldM (\ cf idx -> locateInstance idx ndxs cf) conf idxs
111 86c346db Klaus Aehlig
112 a947a583 Klaus Aehlig
113 a947a583 Klaus Aehlig
-- | Greedily clear a node of a kind of instances by a given relocation method.
114 a947a583 Klaus Aehlig
-- The arguments are a function providing the list of instances to be cleared,
115 a947a583 Klaus Aehlig
-- the relocation function, the list of nodes to be cleared, a list of nodes
116 a947a583 Klaus Aehlig
-- that can be relocated to, and the initial configuration. Returned is a list
117 a947a583 Klaus Aehlig
-- of nodes that can be cleared simultaneously and the configuration after
118 a947a583 Klaus Aehlig
-- clearing these nodes.
119 a947a583 Klaus Aehlig
greedyClearNodes :: ((Node.List, Instance.List) -> Ndx -> [Idx])
120 a947a583 Klaus Aehlig
                    -> ([Idx] -> [Ndx] -> (Node.List, Instance.List)
121 a947a583 Klaus Aehlig
                        -> Result (Node.List, Instance.List))
122 a947a583 Klaus Aehlig
                    -> [Ndx] -> [Ndx] -> (Node.List, Instance.List)
123 a947a583 Klaus Aehlig
                    -> Result ([Ndx], (Node.List, Instance.List))
124 a947a583 Klaus Aehlig
greedyClearNodes  _ _ [] _ conf = return ([], conf)
125 a947a583 Klaus Aehlig
greedyClearNodes getInstances relocate (ndx:ndxs) targets conf@(nl, _) =
126 f2e50930 Klaus Aehlig
  withFirst `mplus` withoutFirst where
127 86c346db Klaus Aehlig
  withFirst = do
128 86c346db Klaus Aehlig
     let othernodes = delete ndx targets
129 f2e50930 Klaus Aehlig
         grp = Node.group $ Container.find ndx nl
130 f2e50930 Klaus Aehlig
         othernodesSameGroup =
131 f2e50930 Klaus Aehlig
           filter ((==) grp . Node.group . flip Container.find nl) othernodes
132 a947a583 Klaus Aehlig
     conf' <- relocate (getInstances conf ndx) othernodesSameGroup conf
133 a947a583 Klaus Aehlig
     (ndxs', conf'') <- greedyClearNodes getInstances relocate
134 a947a583 Klaus Aehlig
                        ndxs othernodes conf'
135 86c346db Klaus Aehlig
     return (ndx:ndxs', conf'')
136 a947a583 Klaus Aehlig
  withoutFirst = greedyClearNodes getInstances relocate ndxs targets conf
137 a947a583 Klaus Aehlig
                    
138 a947a583 Klaus Aehlig
-- | Greedily move the non-redundant instances away from a list of nodes.
139 a947a583 Klaus Aehlig
-- Returns a list of ndoes that can be cleared simultaneously and the
140 a947a583 Klaus Aehlig
-- configuration after clearing these nodes.
141 a947a583 Klaus Aehlig
clearNodes :: [Ndx] -> [Ndx] -> (Node.List, Instance.List)
142 a947a583 Klaus Aehlig
              -> Result ([Ndx], (Node.List, Instance.List))
143 a947a583 Klaus Aehlig
clearNodes = greedyClearNodes nonRedundant locateInstances
144 86c346db Klaus Aehlig
145 fdbdeaa3 Klaus Aehlig
-- | Partition nodes according to some clearing strategy.
146 fdbdeaa3 Klaus Aehlig
-- Arguments are the clearing strategy, the list of nodes to be cleared,
147 fdbdeaa3 Klaus Aehlig
-- the list of nodes that instances can be moved to, and the initial
148 fdbdeaa3 Klaus Aehlig
-- configuration. Returned is a partion of the nodes to be cleared with the
149 fdbdeaa3 Klaus Aehlig
-- configuration in that clearing situation.
150 fdbdeaa3 Klaus Aehlig
partitionNodes :: ([Ndx] -> [Ndx] -> (Node.List, Instance.List)
151 fdbdeaa3 Klaus Aehlig
                   -> Result ([Ndx], (Node.List, Instance.List)))
152 fdbdeaa3 Klaus Aehlig
                  -> [Ndx] -> [Ndx] -> (Node.List, Instance.List)
153 fdbdeaa3 Klaus Aehlig
                  -> Result [([Ndx], (Node.List, Instance.List))]
154 fdbdeaa3 Klaus Aehlig
partitionNodes _ [] _  _ = return []
155 fdbdeaa3 Klaus Aehlig
partitionNodes clear ndxs targets conf = do
156 fdbdeaa3 Klaus Aehlig
  (grp, conf') <- clear ndxs targets conf
157 86c346db Klaus Aehlig
  guard . not . null $ grp
158 86c346db Klaus Aehlig
  let remaining = ndxs \\ grp
159 fdbdeaa3 Klaus Aehlig
  part <- partitionNodes clear remaining targets conf
160 30ce253e Klaus Aehlig
  return $ (grp, conf') : part
161 86c346db Klaus Aehlig
162 fdbdeaa3 Klaus Aehlig
-- | Parition a list of nodes into chunks according cluster capacity.
163 fdbdeaa3 Klaus Aehlig
partitionNonRedundant :: [Ndx] -> [Ndx] -> (Node.List, Instance.List)
164 fdbdeaa3 Klaus Aehlig
                         -> Result [([Ndx], (Node.List, Instance.List))]
165 fdbdeaa3 Klaus Aehlig
partitionNonRedundant = partitionNodes clearNodes
166 fdbdeaa3 Klaus Aehlig
167 a12b230c Klaus Aehlig
-- | Compute the result of migrating an instance.
168 a12b230c Klaus Aehlig
migrate :: Idx -> (Node.List, Instance.List)
169 a12b230c Klaus Aehlig
           -> OpResult (Node.List, Instance.List)
170 a12b230c Klaus Aehlig
migrate idx (nl, il) = do
171 a12b230c Klaus Aehlig
  let inst = Container.find idx il
172 a12b230c Klaus Aehlig
      pdx = Instance.pNode inst
173 a12b230c Klaus Aehlig
      sdx = Instance.sNode inst
174 a12b230c Klaus Aehlig
      pNode = Container.find pdx nl
175 a12b230c Klaus Aehlig
      sNode = Container.find sdx nl
176 a12b230c Klaus Aehlig
      pNode' = Node.removePri pNode inst
177 a12b230c Klaus Aehlig
      sNode' = Node.removeSec sNode inst
178 a12b230c Klaus Aehlig
  sNode'' <- Node.addPriEx True sNode' inst
179 a12b230c Klaus Aehlig
  pNode'' <- Node.addSecEx True pNode' inst sdx
180 a12b230c Klaus Aehlig
  let inst' = Instance.setBoth inst sdx pdx
181 a12b230c Klaus Aehlig
      nl' = Container.addTwo pdx pNode'' sdx sNode'' nl
182 a12b230c Klaus Aehlig
      il' = Container.add idx inst' il
183 a12b230c Klaus Aehlig
  return (nl', il')
184 a12b230c Klaus Aehlig
185 a12b230c Klaus Aehlig
-- | Obtain the list of primaries for a given node.
186 a12b230c Klaus Aehlig
-- This restricts to those instances that have a secondary node.
187 a12b230c Klaus Aehlig
primaries :: (Node.List, Instance.List) -> Ndx -> [Idx]
188 a12b230c Klaus Aehlig
primaries (nl, il) = 
189 a12b230c Klaus Aehlig
  filter (Instance.hasSecondary . flip Container.find  il) 
190 a12b230c Klaus Aehlig
  . Node.pList . flip Container.find nl
191 a12b230c Klaus Aehlig
192 a12b230c Klaus Aehlig
-- | Migrate all instances of a given list of nodes.
193 a12b230c Klaus Aehlig
-- The list of nodes is repeated as first argument in the result.
194 a12b230c Klaus Aehlig
migrateOffNodes :: ([Ndx], (Node.List, Instance.List))
195 a12b230c Klaus Aehlig
                   -> OpResult ([Ndx], (Node.List, Instance.List))
196 a12b230c Klaus Aehlig
migrateOffNodes (ndxs, conf) = do
197 a12b230c Klaus Aehlig
  let instances = ndxs >>= primaries conf
198 a12b230c Klaus Aehlig
  conf' <- foldM (flip migrate) conf instances
199 a12b230c Klaus Aehlig
  return (ndxs, conf')
200 a12b230c Klaus Aehlig
201 a12b230c Klaus Aehlig
-- | Compute the result of replacing the secondary node of an instance.
202 a12b230c Klaus Aehlig
replaceSecondary :: Idx -> Ndx -> (Node.List, Instance.List)
203 a12b230c Klaus Aehlig
        -> OpResult (Node.List, Instance.List)
204 a12b230c Klaus Aehlig
replaceSecondary idx new_ndx (nl, il) = do
205 a12b230c Klaus Aehlig
  let  new_secondary = Container.find new_ndx nl
206 a12b230c Klaus Aehlig
       inst = Container.find idx il
207 a12b230c Klaus Aehlig
       old_ndx = Instance.sNode inst
208 a12b230c Klaus Aehlig
       pdx = Instance.pNode inst
209 a12b230c Klaus Aehlig
       old_secondary = Container.find pdx nl
210 a12b230c Klaus Aehlig
  if pdx == new_ndx then Bad FailInternal else Ok ()
211 a12b230c Klaus Aehlig
  new_secondary' <- Node.addSecEx True new_secondary inst pdx
212 a12b230c Klaus Aehlig
  let old_secondary' = Node.removeSec old_secondary inst
213 a12b230c Klaus Aehlig
      inst' = Instance.setSec inst new_ndx
214 a12b230c Klaus Aehlig
      nl' = Container.addTwo old_ndx old_secondary' new_ndx new_secondary' nl
215 a12b230c Klaus Aehlig
      il' = Container.add idx inst' il
216 a12b230c Klaus Aehlig
  return (nl', il')
217 a12b230c Klaus Aehlig
218 a12b230c Klaus Aehlig
-- | Find a suitable secondary node for the given instance from a list of nodes.
219 a12b230c Klaus Aehlig
findSecondary :: Idx -> [Ndx] -> (Node.List, Instance.List)
220 a12b230c Klaus Aehlig
                 -> Result (Node.List, Instance.List)
221 a12b230c Klaus Aehlig
findSecondary idx ndxs conf =
222 a12b230c Klaus Aehlig
  msum $ map (opToResult . flip (replaceSecondary idx) conf) ndxs
223 a12b230c Klaus Aehlig
224 a12b230c Klaus Aehlig
-- | Find suitable secondary nodes from the given nodes for a list of instances.
225 a12b230c Klaus Aehlig
findSecondaries :: [Idx] -> [Ndx] -> (Node.List, Instance.List) 
226 a12b230c Klaus Aehlig
                   -> Result (Node.List, Instance.List)
227 a12b230c Klaus Aehlig
findSecondaries idxs ndxs conf =
228 a12b230c Klaus Aehlig
  foldM (\ cf idx -> findSecondary idx ndxs cf) conf idxs
229 a12b230c Klaus Aehlig
230 a12b230c Klaus Aehlig
-- | Obtain the list of secondaries for a given node.
231 a12b230c Klaus Aehlig
secondaries :: (Node.List, Instance.List) -> Ndx -> [Idx]
232 a12b230c Klaus Aehlig
secondaries (nl, _) = Node.sList . flip Container.find nl
233 a12b230c Klaus Aehlig
234 a12b230c Klaus Aehlig
-- | Greedily move secondaries away from a list of nodes.
235 a12b230c Klaus Aehlig
-- Returns a list of nodes that can be cleared simultaneously, 
236 a12b230c Klaus Aehlig
-- and the configuration after these nodes are cleared.
237 a12b230c Klaus Aehlig
clearSecondaries :: [Ndx] -> [Ndx] -> (Node.List, Instance.List)
238 a12b230c Klaus Aehlig
                    -> Result ([Ndx], (Node.List, Instance.List))
239 a12b230c Klaus Aehlig
clearSecondaries = greedyClearNodes secondaries findSecondaries
240 a12b230c Klaus Aehlig
241 a12b230c Klaus Aehlig
-- | Partition a list of nodes into chunks according to the ability to find
242 a12b230c Klaus Aehlig
-- suitable replacement secondary nodes.
243 a12b230c Klaus Aehlig
partitionSecondaries :: [Ndx] -> [Ndx] -> (Node.List, Instance.List)
244 a12b230c Klaus Aehlig
                        -> Result [([Ndx], (Node.List, Instance.List))]
245 a12b230c Klaus Aehlig
partitionSecondaries = partitionNodes clearSecondaries
246 a12b230c Klaus Aehlig
247 1a9eb17e Guido Trotter
-- | Gather statistics for the coloring algorithms.
248 1a9eb17e Guido Trotter
-- Returns a string with a summary on how each algorithm has performed,
249 1a9eb17e Guido Trotter
-- in order of non-decreasing effectiveness, and whether it tied or lost
250 1a9eb17e Guido Trotter
-- with the previous one.
251 1a9eb17e Guido Trotter
getStats :: [(String, ColorVertMap)] -> String
252 1a9eb17e Guido Trotter
getStats colorings = snd . foldr helper (0,"") $ algBySize colorings
253 1a9eb17e Guido Trotter
    where algostat (algo, cmap) = algo ++ ": " ++ size cmap ++ grpsizes cmap
254 1a9eb17e Guido Trotter
          size cmap = show (IntMap.size cmap) ++ " "
255 1a9eb17e Guido Trotter
          grpsizes cmap =
256 1a9eb17e Guido Trotter
            "(" ++ commaJoin (map (show.length) (IntMap.elems cmap)) ++ ")"
257 1a9eb17e Guido Trotter
          algBySize = sortBy (flip (comparing (IntMap.size.snd)))
258 1a9eb17e Guido Trotter
          helper :: (String, ColorVertMap) -> (Int, String) -> (Int, String)
259 1a9eb17e Guido Trotter
          helper el (0, _) = ((IntMap.size.snd) el, algostat el)
260 1a9eb17e Guido Trotter
          helper el (old, str)
261 1a9eb17e Guido Trotter
            | old == elsize = (elsize, str ++ " TIE " ++ algostat el)
262 1a9eb17e Guido Trotter
            | otherwise = (elsize, str ++ " LOOSE " ++ algostat el)
263 1a9eb17e Guido Trotter
              where elsize = (IntMap.size.snd) el
264 1a9eb17e Guido Trotter
265 442d5aae Klaus Aehlig
-- | Predicate of belonging to a given group restriction.
266 442d5aae Klaus Aehlig
hasGroup :: Maybe Group.Group -> Node.Node -> Bool
267 442d5aae Klaus Aehlig
hasGroup Nothing _ = True
268 3409c0af Klaus Aehlig
hasGroup (Just grp) node = Node.group node == Group.idx grp
269 544029d3 Guido Trotter
270 313fdabc Klaus Aehlig
-- | Predicate of having at least one tag in a given set.
271 313fdabc Klaus Aehlig
hasTag :: Maybe [String] -> Node.Node -> Bool
272 313fdabc Klaus Aehlig
hasTag Nothing _ = True
273 313fdabc Klaus Aehlig
hasTag (Just tags) node = not . null $ Node.nTags node `intersect` tags
274 313fdabc Klaus Aehlig
275 89363f98 Klaus Aehlig
-- | From a cluster configuration, get the list of non-redundant instances
276 89363f98 Klaus Aehlig
-- of a node.
277 89363f98 Klaus Aehlig
nonRedundant :: (Node.List, Instance.List) -> Ndx -> [Idx]
278 89363f98 Klaus Aehlig
nonRedundant (nl, il) ndx =
279 89363f98 Klaus Aehlig
  filter (not . Instance.hasSecondary . flip Container.find  il) $
280 89363f98 Klaus Aehlig
  Node.pList (Container.find ndx nl)
281 89363f98 Klaus Aehlig
282 89363f98 Klaus Aehlig
-- | Within a cluster configuration, decide if the node hosts non-redundant
283 89363f98 Klaus Aehlig
-- Instances.
284 89363f98 Klaus Aehlig
noNonRedundant :: (Node.List, Instance.List) -> Node.Node -> Bool
285 89363f98 Klaus Aehlig
noNonRedundant conf = null . nonRedundant conf . Node.idx
286 89363f98 Klaus Aehlig
287 5b658b83 Klaus Aehlig
-- | Put the master node last.
288 30ce253e Klaus Aehlig
-- Reorder a list groups of nodes (with additional information) such that the
289 30ce253e Klaus Aehlig
-- master node (if present) is the last node of the last group.
290 30ce253e Klaus Aehlig
masterLast :: [([Node.Node], a)] -> [([Node.Node], a)]
291 5b658b83 Klaus Aehlig
masterLast rebootgroups =
292 30ce253e Klaus Aehlig
  map (first $ uncurry (++)) . uncurry (++) . partition (null . snd . fst) $
293 30ce253e Klaus Aehlig
  map (first $ partition (not . Node.isMaster)) rebootgroups
294 30ce253e Klaus Aehlig
295 30ce253e Klaus Aehlig
-- | From two configurations compute the list of moved instances.
296 a12b230c Klaus Aehlig
-- Do not show instances where only primary and secondary switched their
297 a12b230c Klaus Aehlig
-- role, as here the instance is not moved in a proper sense.
298 30ce253e Klaus Aehlig
getMoves :: (Node.List, Instance.List) -> (Node.List, Instance.List)
299 a12b230c Klaus Aehlig
            -> [(Instance.Instance, (Node.Node, Maybe Node.Node))]
300 30ce253e Klaus Aehlig
getMoves (_, il) (nl', il') = do
301 30ce253e Klaus Aehlig
  ix <- Container.keys il
302 30ce253e Klaus Aehlig
  let inst = Container.find ix il
303 30ce253e Klaus Aehlig
      inst' = Container.find ix il'
304 a12b230c Klaus Aehlig
      hasSec = Instance.hasSecondary inst
305 30ce253e Klaus Aehlig
  guard $ Instance.pNode inst /= Instance.pNode inst'
306 a12b230c Klaus Aehlig
          || (hasSec && Instance.sNode inst /= Instance.sNode inst')
307 a12b230c Klaus Aehlig
  guard . not $ Instance.pNode inst' == Instance.sNode inst
308 a12b230c Klaus Aehlig
                && Instance.sNode inst' == Instance.pNode inst
309 a12b230c Klaus Aehlig
  return (inst', (Container.find (Instance.pNode inst') nl', 
310 a12b230c Klaus Aehlig
                  if hasSec
311 a12b230c Klaus Aehlig
                     then Just $ Container.find (Instance.sNode inst') nl'
312 a12b230c Klaus Aehlig
                     else Nothing))
313 5b658b83 Klaus Aehlig
314 3504d6c8 Guido Trotter
-- | Main function.
315 3504d6c8 Guido Trotter
main :: Options -> [String] -> IO ()
316 1a9eb17e Guido Trotter
main opts args = do
317 1a9eb17e Guido Trotter
  unless (null args) $ exitErr "This program doesn't take any arguments."
318 1a9eb17e Guido Trotter
319 1a9eb17e Guido Trotter
  let verbose = optVerbose opts
320 7dbe4c72 Klaus Aehlig
      maybeExit = if optForce opts then warn else exitErr
321 1a9eb17e Guido Trotter
322 1a9eb17e Guido Trotter
  -- Load cluster data. The last two arguments, cluster tags and ipolicy, are
323 1a9eb17e Guido Trotter
  -- currently not used by this tool.
324 2fce67b6 Guido Trotter
  ini_cdata@(ClusterData gl fixed_nl ilf _ _) <- loadExternalData opts
325 1a9eb17e Guido Trotter
326 7dbe4c72 Klaus Aehlig
  let master_names = map Node.name . filter Node.isMaster . IntMap.elems $
327 7dbe4c72 Klaus Aehlig
                     fixed_nl
328 7dbe4c72 Klaus Aehlig
  case master_names of
329 7dbe4c72 Klaus Aehlig
    [] -> maybeExit "No master node found (maybe not supported by backend)."
330 7dbe4c72 Klaus Aehlig
    [ _ ] -> return ()
331 7dbe4c72 Klaus Aehlig
    _ -> exitErr $ "Found more than one master node: " ++  show master_names
332 7dbe4c72 Klaus Aehlig
333 1a9eb17e Guido Trotter
  nlf <- setNodeStatus opts fixed_nl
334 1a9eb17e Guido Trotter
335 1a9eb17e Guido Trotter
  maybeSaveData (optSaveCluster opts) "original" "before hroller run" ini_cdata
336 1a9eb17e Guido Trotter
337 2fce67b6 Guido Trotter
  -- Find the wanted node group, if any.
338 2fce67b6 Guido Trotter
  wantedGroup <- case optGroup opts of
339 2fce67b6 Guido Trotter
    Nothing -> return Nothing
340 2fce67b6 Guido Trotter
    Just name -> case Container.findByName gl name of
341 2fce67b6 Guido Trotter
      Nothing -> exitErr "Cannot find target group."
342 2fce67b6 Guido Trotter
      Just grp -> return (Just grp)
343 2fce67b6 Guido Trotter
344 313fdabc Klaus Aehlig
  let nodes = IntMap.filter (foldl (liftA2 (&&)) (const True)
345 3409c0af Klaus Aehlig
                             [ not . Node.offline
346 89363f98 Klaus Aehlig
                             , if optSkipNonRedundant opts
347 89363f98 Klaus Aehlig
                                  then noNonRedundant (nlf, ilf)
348 89363f98 Klaus Aehlig
                                  else const True
349 004398d0 Klaus Aehlig
                             , hasTag $ optNodeTags opts
350 313fdabc Klaus Aehlig
                             , hasGroup wantedGroup ])
351 442d5aae Klaus Aehlig
              nlf
352 8d38fb72 Klaus Aehlig
      mkGraph = if optOfflineMaintenance opts
353 8d38fb72 Klaus Aehlig
                   then Node.mkNodeGraph
354 8d38fb72 Klaus Aehlig
                   else Node.mkRebootNodeGraph nlf
355 442d5aae Klaus Aehlig
356 8d38fb72 Klaus Aehlig
  nodeGraph <- case mkGraph nodes ilf of
357 1a9eb17e Guido Trotter
                     Nothing -> exitErr "Cannot create node graph"
358 1a9eb17e Guido Trotter
                     Just g -> return g
359 1a9eb17e Guido Trotter
360 1a9eb17e Guido Trotter
  when (verbose > 2) . putStrLn $ "Node Graph: " ++ show nodeGraph
361 1a9eb17e Guido Trotter
362 1a9eb17e Guido Trotter
  let colorAlgorithms = [ ("LF", colorLF)
363 1a9eb17e Guido Trotter
                        , ("Dsatur", colorDsatur)
364 1a9eb17e Guido Trotter
                        , ("Dcolor", colorDcolor)
365 1a9eb17e Guido Trotter
                        ]
366 1a9eb17e Guido Trotter
      colorings = map (\(v,a) -> (v,(colorVertMap.a) nodeGraph)) colorAlgorithms
367 23247a73 Klaus Aehlig
      smallestColoring = IntMap.elems $
368 1a9eb17e Guido Trotter
        (snd . minimumBy (comparing (IntMap.size . snd))) colorings
369 634a1460 Klaus Aehlig
      allNdx = map Node.idx . filter (not . Node.offline) . Container.elems
370 634a1460 Klaus Aehlig
               $ nlf
371 23247a73 Klaus Aehlig
      splitted = mapM (\ grp -> partitionNonRedundant grp allNdx (nlf,ilf))
372 23247a73 Klaus Aehlig
                 smallestColoring
373 23247a73 Klaus Aehlig
  rebootGroups <- if optIgnoreNonRedundant opts
374 30ce253e Klaus Aehlig
                     then return $ zip smallestColoring (repeat (nlf, ilf))
375 23247a73 Klaus Aehlig
                     else case splitted of
376 23247a73 Klaus Aehlig
                            Ok splitgroups -> return $ concat splitgroups
377 23247a73 Klaus Aehlig
                            Bad _ -> exitErr "Not enough capacity to move\ 
378 23247a73 Klaus Aehlig
                                             \ non-redundant instances"
379 a12b230c Klaus Aehlig
  
380 a12b230c Klaus Aehlig
  let migrated = mapM migrateOffNodes rebootGroups
381 a12b230c Klaus Aehlig
  rebootGroups' <- if not . optFullEvacuation $ opts
382 a12b230c Klaus Aehlig
                      then return rebootGroups
383 a12b230c Klaus Aehlig
                      else case migrated of
384 a12b230c Klaus Aehlig
                             Ok migratedGroup -> return migratedGroup
385 a12b230c Klaus Aehlig
                             Bad _ -> exitErr "Failed to migrate instances\ 
386 a12b230c Klaus Aehlig
                                              \ off nodes"
387 a12b230c Klaus Aehlig
  let splitted' = mapM (\(grp, conf) -> partitionSecondaries grp allNdx conf)
388 a12b230c Klaus Aehlig
                  rebootGroups'
389 a12b230c Klaus Aehlig
  rebootGroups'' <- if optFullEvacuation opts
390 a12b230c Klaus Aehlig
                      then case splitted' of
391 a12b230c Klaus Aehlig
                             Ok splitgroups -> return $ concat splitgroups
392 a12b230c Klaus Aehlig
                             Bad _ -> exitErr "Not enough capacity to move\
393 a12b230c Klaus Aehlig
                                              \ secondaries"
394 a12b230c Klaus Aehlig
                      else return rebootGroups'
395 86c346db Klaus Aehlig
  let idToNode = (`Container.find` nodes)
396 a12b230c Klaus Aehlig
      nodesRebootGroups = map (first $ map idToNode
397 a12b230c Klaus Aehlig
                                       . filter (`IntMap.member` nodes))
398 a12b230c Klaus Aehlig
                          rebootGroups''
399 a39779f6 Klaus Aehlig
      outputRebootGroups = masterLast .
400 30ce253e Klaus Aehlig
                           sortBy (flip compare `on` length . fst) $
401 a39779f6 Klaus Aehlig
                           nodesRebootGroups
402 a12b230c Klaus Aehlig
      confToMoveNames =
403 a12b230c Klaus Aehlig
        map (Instance.name *** (Node.name *** flip (>>=) (return . Node.name)))
404 a12b230c Klaus Aehlig
        . getMoves (nlf, ilf)
405 30ce253e Klaus Aehlig
      namesAndMoves = map (map Node.name *** confToMoveNames) outputRebootGroups
406 1a9eb17e Guido Trotter
407 1a9eb17e Guido Trotter
  when (verbose > 1) . putStrLn $ getStats colorings
408 1a9eb17e Guido Trotter
409 30ce253e Klaus Aehlig
  let showGroup = if optOneStepOnly opts
410 30ce253e Klaus Aehlig
                    then mapM_ putStrLn
411 30ce253e Klaus Aehlig
                    else putStrLn . commaJoin
412 a12b230c Klaus Aehlig
      showMoves :: [(String, (String, Maybe String))] -> IO ()
413 30ce253e Klaus Aehlig
      showMoves = if optPrintMoves opts
414 a12b230c Klaus Aehlig
                    then mapM_ $ putStrLn . \(a,(b,c)) ->
415 a12b230c Klaus Aehlig
                                                maybe (printf "  %s %s" a b)
416 a12b230c Klaus Aehlig
                                                      (printf "  %s %s %s" a b)
417 a12b230c Klaus Aehlig
                                                      c
418 30ce253e Klaus Aehlig
                    else const $ return ()
419 30ce253e Klaus Aehlig
      showBoth = liftM2 (>>) (showGroup . fst) (showMoves . snd)
420 30ce253e Klaus Aehlig
421 30ce253e Klaus Aehlig
422 2207220d Klaus Aehlig
  if optOneStepOnly opts
423 2207220d Klaus Aehlig
     then do
424 2207220d Klaus Aehlig
       unless (optNoHeaders opts) $
425 2207220d Klaus Aehlig
              putStrLn "'First Reboot Group'"
426 30ce253e Klaus Aehlig
       case namesAndMoves of
427 2207220d Klaus Aehlig
         [] -> return ()
428 30ce253e Klaus Aehlig
         y : _ -> showBoth y
429 2207220d Klaus Aehlig
     else do
430 2207220d Klaus Aehlig
       unless (optNoHeaders opts) $
431 2207220d Klaus Aehlig
              putStrLn "'Node Reboot Groups'"
432 30ce253e Klaus Aehlig
       mapM_ showBoth namesAndMoves