Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hroller.hs @ a8cbe1d7

History | View | Annotate | Download (11.1 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 89363f98 Klaus Aehlig
    , oSkipNonRedundant
75 23247a73 Klaus Aehlig
    , oIgnoreNonRedundant
76 7dbe4c72 Klaus Aehlig
    , oForce
77 2207220d Klaus Aehlig
    , oOneStepOnly
78 3504d6c8 Guido Trotter
    ]
79 3504d6c8 Guido Trotter
80 3504d6c8 Guido Trotter
-- | The list of arguments supported by the program.
81 3504d6c8 Guido Trotter
arguments :: [ArgCompletion]
82 3504d6c8 Guido Trotter
arguments = []
83 3504d6c8 Guido Trotter
84 86c346db Klaus Aehlig
-- | Compute the result of moving an instance to a different node.
85 86c346db Klaus Aehlig
move :: Idx -> Ndx -> (Node.List, Instance.List)
86 86c346db Klaus Aehlig
        -> OpResult (Node.List, Instance.List)
87 86c346db Klaus Aehlig
move idx new_ndx (nl, il) = do
88 86c346db Klaus Aehlig
  let new_node = Container.find new_ndx nl
89 86c346db Klaus Aehlig
      inst = Container.find idx il
90 86c346db Klaus Aehlig
      old_ndx = Instance.pNode inst
91 86c346db Klaus Aehlig
      old_node = Container.find old_ndx nl
92 86c346db Klaus Aehlig
  new_node' <- Node.addPriEx True new_node inst
93 86c346db Klaus Aehlig
  let old_node' = Node.removePri old_node inst
94 86c346db Klaus Aehlig
      inst' = Instance.setPri inst new_ndx
95 86c346db Klaus Aehlig
      nl' = Container.addTwo old_ndx old_node' new_ndx new_node' nl
96 86c346db Klaus Aehlig
      il' = Container.add idx inst' il
97 86c346db Klaus Aehlig
  return (nl', il')
98 86c346db Klaus Aehlig
99 a8cbe1d7 Klaus Aehlig
-- | Move a non-redundant instance to one of the candidate nodes mentioned.
100 86c346db Klaus Aehlig
locateInstance :: Idx -> [Ndx] -> (Node.List, Instance.List)
101 86c346db Klaus Aehlig
                  -> Result (Node.List, Instance.List)
102 86c346db Klaus Aehlig
locateInstance idx ndxs conf =
103 86c346db Klaus Aehlig
  msum $ map (opToResult . flip (move idx) conf) ndxs
104 86c346db Klaus Aehlig
105 a8cbe1d7 Klaus Aehlig
-- | Move a list of non-redundant instances to some of the nodes mentioned.
106 86c346db Klaus Aehlig
locateInstances :: [Idx] -> [Ndx] -> (Node.List, Instance.List)
107 86c346db Klaus Aehlig
                   -> Result (Node.List, Instance.List)
108 86c346db Klaus Aehlig
locateInstances idxs ndxs conf =
109 86c346db Klaus Aehlig
  foldM (\ cf idx -> locateInstance idx ndxs cf) conf idxs
110 86c346db Klaus Aehlig
111 86c346db Klaus Aehlig
-- | Greedily move the non-redundant instances away from a list of nodes.
112 86c346db Klaus Aehlig
-- The arguments are the list of nodes to be cleared, a list of nodes the
113 86c346db Klaus Aehlig
-- instances can be moved to, and an initial configuration. Returned is a
114 86c346db Klaus Aehlig
-- list of nodes that can be cleared simultaneously and the configuration
115 86c346db Klaus Aehlig
-- after these nodes are cleared.
116 86c346db Klaus Aehlig
clearNodes :: [Ndx] -> [Ndx] -> (Node.List, Instance.List)
117 86c346db Klaus Aehlig
              -> Result ([Ndx], (Node.List, Instance.List))
118 86c346db Klaus Aehlig
clearNodes [] _ conf = return ([], conf)
119 f2e50930 Klaus Aehlig
clearNodes (ndx:ndxs) targets conf@(nl, _) =
120 f2e50930 Klaus Aehlig
  withFirst `mplus` withoutFirst where
121 86c346db Klaus Aehlig
  withFirst = do
122 86c346db Klaus Aehlig
     let othernodes = delete ndx targets
123 f2e50930 Klaus Aehlig
         grp = Node.group $ Container.find ndx nl
124 f2e50930 Klaus Aehlig
         othernodesSameGroup =
125 f2e50930 Klaus Aehlig
           filter ((==) grp . Node.group . flip Container.find nl) othernodes
126 f2e50930 Klaus Aehlig
     conf' <- locateInstances (nonRedundant conf ndx) othernodesSameGroup conf
127 86c346db Klaus Aehlig
     (ndxs', conf'') <- clearNodes ndxs othernodes conf'
128 86c346db Klaus Aehlig
     return (ndx:ndxs', conf'')
129 86c346db Klaus Aehlig
  withoutFirst = clearNodes ndxs targets conf
130 86c346db Klaus Aehlig
131 86c346db Klaus Aehlig
-- | Parition a list of nodes into chunks according cluster capacity.
132 86c346db Klaus Aehlig
partitionNonRedundant :: [Ndx] -> [Ndx] -> (Node.List, Instance.List)
133 30ce253e Klaus Aehlig
                         -> Result [([Ndx], (Node.List, Instance.List))]
134 86c346db Klaus Aehlig
partitionNonRedundant [] _ _ = return []
135 86c346db Klaus Aehlig
partitionNonRedundant ndxs targets conf = do
136 30ce253e Klaus Aehlig
  (grp, conf') <- clearNodes ndxs targets conf
137 86c346db Klaus Aehlig
  guard . not . null $ grp
138 86c346db Klaus Aehlig
  let remaining = ndxs \\ grp
139 86c346db Klaus Aehlig
  part <- partitionNonRedundant remaining targets conf
140 30ce253e Klaus Aehlig
  return $ (grp, conf') : part
141 86c346db Klaus Aehlig
142 1a9eb17e Guido Trotter
-- | Gather statistics for the coloring algorithms.
143 1a9eb17e Guido Trotter
-- Returns a string with a summary on how each algorithm has performed,
144 1a9eb17e Guido Trotter
-- in order of non-decreasing effectiveness, and whether it tied or lost
145 1a9eb17e Guido Trotter
-- with the previous one.
146 1a9eb17e Guido Trotter
getStats :: [(String, ColorVertMap)] -> String
147 1a9eb17e Guido Trotter
getStats colorings = snd . foldr helper (0,"") $ algBySize colorings
148 1a9eb17e Guido Trotter
    where algostat (algo, cmap) = algo ++ ": " ++ size cmap ++ grpsizes cmap
149 1a9eb17e Guido Trotter
          size cmap = show (IntMap.size cmap) ++ " "
150 1a9eb17e Guido Trotter
          grpsizes cmap =
151 1a9eb17e Guido Trotter
            "(" ++ commaJoin (map (show.length) (IntMap.elems cmap)) ++ ")"
152 1a9eb17e Guido Trotter
          algBySize = sortBy (flip (comparing (IntMap.size.snd)))
153 1a9eb17e Guido Trotter
          helper :: (String, ColorVertMap) -> (Int, String) -> (Int, String)
154 1a9eb17e Guido Trotter
          helper el (0, _) = ((IntMap.size.snd) el, algostat el)
155 1a9eb17e Guido Trotter
          helper el (old, str)
156 1a9eb17e Guido Trotter
            | old == elsize = (elsize, str ++ " TIE " ++ algostat el)
157 1a9eb17e Guido Trotter
            | otherwise = (elsize, str ++ " LOOSE " ++ algostat el)
158 1a9eb17e Guido Trotter
              where elsize = (IntMap.size.snd) el
159 1a9eb17e Guido Trotter
160 442d5aae Klaus Aehlig
-- | Predicate of belonging to a given group restriction.
161 442d5aae Klaus Aehlig
hasGroup :: Maybe Group.Group -> Node.Node -> Bool
162 442d5aae Klaus Aehlig
hasGroup Nothing _ = True
163 3409c0af Klaus Aehlig
hasGroup (Just grp) node = Node.group node == Group.idx grp
164 544029d3 Guido Trotter
165 313fdabc Klaus Aehlig
-- | Predicate of having at least one tag in a given set.
166 313fdabc Klaus Aehlig
hasTag :: Maybe [String] -> Node.Node -> Bool
167 313fdabc Klaus Aehlig
hasTag Nothing _ = True
168 313fdabc Klaus Aehlig
hasTag (Just tags) node = not . null $ Node.nTags node `intersect` tags
169 313fdabc Klaus Aehlig
170 89363f98 Klaus Aehlig
-- | From a cluster configuration, get the list of non-redundant instances
171 89363f98 Klaus Aehlig
-- of a node.
172 89363f98 Klaus Aehlig
nonRedundant :: (Node.List, Instance.List) -> Ndx -> [Idx]
173 89363f98 Klaus Aehlig
nonRedundant (nl, il) ndx =
174 89363f98 Klaus Aehlig
  filter (not . Instance.hasSecondary . flip Container.find  il) $
175 89363f98 Klaus Aehlig
  Node.pList (Container.find ndx nl)
176 89363f98 Klaus Aehlig
177 89363f98 Klaus Aehlig
-- | Within a cluster configuration, decide if the node hosts non-redundant
178 89363f98 Klaus Aehlig
-- Instances.
179 89363f98 Klaus Aehlig
noNonRedundant :: (Node.List, Instance.List) -> Node.Node -> Bool
180 89363f98 Klaus Aehlig
noNonRedundant conf = null . nonRedundant conf . Node.idx
181 89363f98 Klaus Aehlig
182 5b658b83 Klaus Aehlig
-- | Put the master node last.
183 30ce253e Klaus Aehlig
-- Reorder a list groups of nodes (with additional information) such that the
184 30ce253e Klaus Aehlig
-- master node (if present) is the last node of the last group.
185 30ce253e Klaus Aehlig
masterLast :: [([Node.Node], a)] -> [([Node.Node], a)]
186 5b658b83 Klaus Aehlig
masterLast rebootgroups =
187 30ce253e Klaus Aehlig
  map (first $ uncurry (++)) . uncurry (++) . partition (null . snd . fst) $
188 30ce253e Klaus Aehlig
  map (first $ partition (not . Node.isMaster)) rebootgroups
189 30ce253e Klaus Aehlig
190 30ce253e Klaus Aehlig
-- | From two configurations compute the list of moved instances.
191 30ce253e Klaus Aehlig
getMoves :: (Node.List, Instance.List) -> (Node.List, Instance.List)
192 30ce253e Klaus Aehlig
            -> [(Instance.Instance, Node.Node)]
193 30ce253e Klaus Aehlig
getMoves (_, il) (nl', il') = do
194 30ce253e Klaus Aehlig
  ix <- Container.keys il
195 30ce253e Klaus Aehlig
  let inst = Container.find ix il
196 30ce253e Klaus Aehlig
      inst' = Container.find ix il'
197 30ce253e Klaus Aehlig
  guard $ Instance.pNode inst /= Instance.pNode inst'
198 30ce253e Klaus Aehlig
  return (inst', Container.find (Instance.pNode inst') nl')
199 5b658b83 Klaus Aehlig
200 3504d6c8 Guido Trotter
-- | Main function.
201 3504d6c8 Guido Trotter
main :: Options -> [String] -> IO ()
202 1a9eb17e Guido Trotter
main opts args = do
203 1a9eb17e Guido Trotter
  unless (null args) $ exitErr "This program doesn't take any arguments."
204 1a9eb17e Guido Trotter
205 1a9eb17e Guido Trotter
  let verbose = optVerbose opts
206 7dbe4c72 Klaus Aehlig
      maybeExit = if optForce opts then warn else exitErr
207 1a9eb17e Guido Trotter
208 1a9eb17e Guido Trotter
  -- Load cluster data. The last two arguments, cluster tags and ipolicy, are
209 1a9eb17e Guido Trotter
  -- currently not used by this tool.
210 2fce67b6 Guido Trotter
  ini_cdata@(ClusterData gl fixed_nl ilf _ _) <- loadExternalData opts
211 1a9eb17e Guido Trotter
212 7dbe4c72 Klaus Aehlig
  let master_names = map Node.name . filter Node.isMaster . IntMap.elems $
213 7dbe4c72 Klaus Aehlig
                     fixed_nl
214 7dbe4c72 Klaus Aehlig
  case master_names of
215 7dbe4c72 Klaus Aehlig
    [] -> maybeExit "No master node found (maybe not supported by backend)."
216 7dbe4c72 Klaus Aehlig
    [ _ ] -> return ()
217 7dbe4c72 Klaus Aehlig
    _ -> exitErr $ "Found more than one master node: " ++  show master_names
218 7dbe4c72 Klaus Aehlig
219 1a9eb17e Guido Trotter
  nlf <- setNodeStatus opts fixed_nl
220 1a9eb17e Guido Trotter
221 1a9eb17e Guido Trotter
  maybeSaveData (optSaveCluster opts) "original" "before hroller run" ini_cdata
222 1a9eb17e Guido Trotter
223 2fce67b6 Guido Trotter
  -- Find the wanted node group, if any.
224 2fce67b6 Guido Trotter
  wantedGroup <- case optGroup opts of
225 2fce67b6 Guido Trotter
    Nothing -> return Nothing
226 2fce67b6 Guido Trotter
    Just name -> case Container.findByName gl name of
227 2fce67b6 Guido Trotter
      Nothing -> exitErr "Cannot find target group."
228 2fce67b6 Guido Trotter
      Just grp -> return (Just grp)
229 2fce67b6 Guido Trotter
230 313fdabc Klaus Aehlig
  let nodes = IntMap.filter (foldl (liftA2 (&&)) (const True)
231 3409c0af Klaus Aehlig
                             [ not . Node.offline
232 89363f98 Klaus Aehlig
                             , if optSkipNonRedundant opts
233 89363f98 Klaus Aehlig
                                  then noNonRedundant (nlf, ilf)
234 89363f98 Klaus Aehlig
                                  else const True
235 004398d0 Klaus Aehlig
                             , hasTag $ optNodeTags opts
236 313fdabc Klaus Aehlig
                             , hasGroup wantedGroup ])
237 442d5aae Klaus Aehlig
              nlf
238 8d38fb72 Klaus Aehlig
      mkGraph = if optOfflineMaintenance opts
239 8d38fb72 Klaus Aehlig
                   then Node.mkNodeGraph
240 8d38fb72 Klaus Aehlig
                   else Node.mkRebootNodeGraph nlf
241 442d5aae Klaus Aehlig
242 8d38fb72 Klaus Aehlig
  nodeGraph <- case mkGraph nodes ilf of
243 1a9eb17e Guido Trotter
                     Nothing -> exitErr "Cannot create node graph"
244 1a9eb17e Guido Trotter
                     Just g -> return g
245 1a9eb17e Guido Trotter
246 1a9eb17e Guido Trotter
  when (verbose > 2) . putStrLn $ "Node Graph: " ++ show nodeGraph
247 1a9eb17e Guido Trotter
248 1a9eb17e Guido Trotter
  let colorAlgorithms = [ ("LF", colorLF)
249 1a9eb17e Guido Trotter
                        , ("Dsatur", colorDsatur)
250 1a9eb17e Guido Trotter
                        , ("Dcolor", colorDcolor)
251 1a9eb17e Guido Trotter
                        ]
252 1a9eb17e Guido Trotter
      colorings = map (\(v,a) -> (v,(colorVertMap.a) nodeGraph)) colorAlgorithms
253 23247a73 Klaus Aehlig
      smallestColoring = IntMap.elems $
254 1a9eb17e Guido Trotter
        (snd . minimumBy (comparing (IntMap.size . snd))) colorings
255 86c346db Klaus Aehlig
      allNdx = map Node.idx $ Container.elems nlf
256 23247a73 Klaus Aehlig
      splitted = mapM (\ grp -> partitionNonRedundant grp allNdx (nlf,ilf))
257 23247a73 Klaus Aehlig
                 smallestColoring
258 23247a73 Klaus Aehlig
  rebootGroups <- if optIgnoreNonRedundant opts
259 30ce253e Klaus Aehlig
                     then return $ zip smallestColoring (repeat (nlf, ilf))
260 23247a73 Klaus Aehlig
                     else case splitted of
261 23247a73 Klaus Aehlig
                            Ok splitgroups -> return $ concat splitgroups
262 23247a73 Klaus Aehlig
                            Bad _ -> exitErr "Not enough capacity to move\ 
263 23247a73 Klaus Aehlig
                                             \ non-redundant instances"
264 86c346db Klaus Aehlig
  let idToNode = (`Container.find` nodes)
265 442d5aae Klaus Aehlig
      nodesRebootGroups =
266 30ce253e Klaus Aehlig
        map (first $ map idToNode . filter (`IntMap.member` nodes)) rebootGroups
267 a39779f6 Klaus Aehlig
      outputRebootGroups = masterLast .
268 30ce253e Klaus Aehlig
                           sortBy (flip compare `on` length . fst) $
269 a39779f6 Klaus Aehlig
                           nodesRebootGroups
270 30ce253e Klaus Aehlig
      confToMoveNames = map (Instance.name *** Node.name) . getMoves (nlf, ilf)
271 30ce253e Klaus Aehlig
      namesAndMoves = map (map Node.name *** confToMoveNames) outputRebootGroups
272 1a9eb17e Guido Trotter
273 1a9eb17e Guido Trotter
  when (verbose > 1) . putStrLn $ getStats colorings
274 1a9eb17e Guido Trotter
275 30ce253e Klaus Aehlig
  let showGroup = if optOneStepOnly opts
276 30ce253e Klaus Aehlig
                    then mapM_ putStrLn
277 30ce253e Klaus Aehlig
                    else putStrLn . commaJoin
278 e7aa0b03 Klaus Aehlig
      showMoves :: [(String, String)] -> IO ()
279 30ce253e Klaus Aehlig
      showMoves = if optPrintMoves opts
280 30ce253e Klaus Aehlig
                    then mapM_ $ putStrLn . uncurry (printf "  %s %s")
281 30ce253e Klaus Aehlig
                    else const $ return ()
282 30ce253e Klaus Aehlig
      showBoth = liftM2 (>>) (showGroup . fst) (showMoves . snd)
283 30ce253e Klaus Aehlig
284 30ce253e Klaus Aehlig
285 2207220d Klaus Aehlig
  if optOneStepOnly opts
286 2207220d Klaus Aehlig
     then do
287 2207220d Klaus Aehlig
       unless (optNoHeaders opts) $
288 2207220d Klaus Aehlig
              putStrLn "'First Reboot Group'"
289 30ce253e Klaus Aehlig
       case namesAndMoves of
290 2207220d Klaus Aehlig
         [] -> return ()
291 30ce253e Klaus Aehlig
         y : _ -> showBoth y
292 2207220d Klaus Aehlig
     else do
293 2207220d Klaus Aehlig
       unless (optNoHeaders opts) $
294 2207220d Klaus Aehlig
              putStrLn "'Node Reboot Groups'"
295 30ce253e Klaus Aehlig
       mapM_ showBoth namesAndMoves