Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hroller.hs @ 3409c0af

History | View | Annotate | Download (6.2 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 1a9eb17e Guido Trotter
import Control.Monad
34 a39779f6 Klaus Aehlig
import Data.Function
35 1a9eb17e Guido Trotter
import Data.List
36 1a9eb17e Guido Trotter
import Data.Ord
37 1a9eb17e Guido Trotter
38 1a9eb17e Guido Trotter
import qualified Data.IntMap as IntMap
39 1a9eb17e Guido Trotter
40 1a9eb17e Guido Trotter
import qualified Ganeti.HTools.Container as Container
41 1a9eb17e Guido Trotter
import qualified Ganeti.HTools.Node as Node
42 2fce67b6 Guido Trotter
import qualified Ganeti.HTools.Group as Group
43 1a9eb17e Guido Trotter
44 3504d6c8 Guido Trotter
import Ganeti.Common
45 3504d6c8 Guido Trotter
import Ganeti.HTools.CLI
46 1a9eb17e Guido Trotter
import Ganeti.HTools.ExtLoader
47 1a9eb17e Guido Trotter
import Ganeti.HTools.Graph
48 1a9eb17e Guido Trotter
import Ganeti.HTools.Loader
49 1a9eb17e Guido Trotter
import Ganeti.Utils
50 3504d6c8 Guido Trotter
51 3504d6c8 Guido Trotter
-- | Options list and functions.
52 3504d6c8 Guido Trotter
options :: IO [OptType]
53 3504d6c8 Guido Trotter
options = do
54 3504d6c8 Guido Trotter
  luxi <- oLuxiSocket
55 3504d6c8 Guido Trotter
  return
56 3504d6c8 Guido Trotter
    [ luxi
57 3504d6c8 Guido Trotter
    , oRapiMaster
58 3504d6c8 Guido Trotter
    , oDataFile
59 3504d6c8 Guido Trotter
    , oIAllocSrc
60 3504d6c8 Guido Trotter
    , oOfflineNode
61 8d38fb72 Klaus Aehlig
    , oOfflineMaintenance
62 3504d6c8 Guido Trotter
    , oVerbose
63 3504d6c8 Guido Trotter
    , oQuiet
64 3504d6c8 Guido Trotter
    , oNoHeaders
65 313fdabc Klaus Aehlig
    , oNodeTags
66 3504d6c8 Guido Trotter
    , oSaveCluster
67 2fce67b6 Guido Trotter
    , oGroup
68 7dbe4c72 Klaus Aehlig
    , oForce
69 2207220d Klaus Aehlig
    , oOneStepOnly
70 3504d6c8 Guido Trotter
    ]
71 3504d6c8 Guido Trotter
72 3504d6c8 Guido Trotter
-- | The list of arguments supported by the program.
73 3504d6c8 Guido Trotter
arguments :: [ArgCompletion]
74 3504d6c8 Guido Trotter
arguments = []
75 3504d6c8 Guido Trotter
76 1a9eb17e Guido Trotter
-- | Gather statistics for the coloring algorithms.
77 1a9eb17e Guido Trotter
-- Returns a string with a summary on how each algorithm has performed,
78 1a9eb17e Guido Trotter
-- in order of non-decreasing effectiveness, and whether it tied or lost
79 1a9eb17e Guido Trotter
-- with the previous one.
80 1a9eb17e Guido Trotter
getStats :: [(String, ColorVertMap)] -> String
81 1a9eb17e Guido Trotter
getStats colorings = snd . foldr helper (0,"") $ algBySize colorings
82 1a9eb17e Guido Trotter
    where algostat (algo, cmap) = algo ++ ": " ++ size cmap ++ grpsizes cmap
83 1a9eb17e Guido Trotter
          size cmap = show (IntMap.size cmap) ++ " "
84 1a9eb17e Guido Trotter
          grpsizes cmap =
85 1a9eb17e Guido Trotter
            "(" ++ commaJoin (map (show.length) (IntMap.elems cmap)) ++ ")"
86 1a9eb17e Guido Trotter
          algBySize = sortBy (flip (comparing (IntMap.size.snd)))
87 1a9eb17e Guido Trotter
          helper :: (String, ColorVertMap) -> (Int, String) -> (Int, String)
88 1a9eb17e Guido Trotter
          helper el (0, _) = ((IntMap.size.snd) el, algostat el)
89 1a9eb17e Guido Trotter
          helper el (old, str)
90 1a9eb17e Guido Trotter
            | old == elsize = (elsize, str ++ " TIE " ++ algostat el)
91 1a9eb17e Guido Trotter
            | otherwise = (elsize, str ++ " LOOSE " ++ algostat el)
92 1a9eb17e Guido Trotter
              where elsize = (IntMap.size.snd) el
93 1a9eb17e Guido Trotter
94 442d5aae Klaus Aehlig
-- | Predicate of belonging to a given group restriction.
95 442d5aae Klaus Aehlig
hasGroup :: Maybe Group.Group -> Node.Node -> Bool
96 442d5aae Klaus Aehlig
hasGroup Nothing _ = True
97 3409c0af Klaus Aehlig
hasGroup (Just grp) node = Node.group node == Group.idx grp
98 544029d3 Guido Trotter
99 313fdabc Klaus Aehlig
-- | Predicate of having at least one tag in a given set.
100 313fdabc Klaus Aehlig
hasTag :: Maybe [String] -> Node.Node -> Bool
101 313fdabc Klaus Aehlig
hasTag Nothing _ = True
102 313fdabc Klaus Aehlig
hasTag (Just tags) node = not . null $ Node.nTags node `intersect` tags
103 313fdabc Klaus Aehlig
104 5b658b83 Klaus Aehlig
-- | Put the master node last.
105 5b658b83 Klaus Aehlig
-- Reorder a list of lists of nodes such that the master node (if present)
106 5b658b83 Klaus Aehlig
-- is the last node of the last group.
107 5b658b83 Klaus Aehlig
masterLast :: [[Node.Node]] -> [[Node.Node]]
108 5b658b83 Klaus Aehlig
masterLast rebootgroups =
109 5b658b83 Klaus Aehlig
  map (uncurry (++)) . uncurry (++) . partition (null . snd) $
110 5b658b83 Klaus Aehlig
  map (partition (not . Node.isMaster)) rebootgroups
111 5b658b83 Klaus Aehlig
112 3504d6c8 Guido Trotter
-- | Main function.
113 3504d6c8 Guido Trotter
main :: Options -> [String] -> IO ()
114 1a9eb17e Guido Trotter
main opts args = do
115 1a9eb17e Guido Trotter
  unless (null args) $ exitErr "This program doesn't take any arguments."
116 1a9eb17e Guido Trotter
117 1a9eb17e Guido Trotter
  let verbose = optVerbose opts
118 7dbe4c72 Klaus Aehlig
      maybeExit = if optForce opts then warn else exitErr
119 1a9eb17e Guido Trotter
120 1a9eb17e Guido Trotter
  -- Load cluster data. The last two arguments, cluster tags and ipolicy, are
121 1a9eb17e Guido Trotter
  -- currently not used by this tool.
122 2fce67b6 Guido Trotter
  ini_cdata@(ClusterData gl fixed_nl ilf _ _) <- loadExternalData opts
123 1a9eb17e Guido Trotter
124 7dbe4c72 Klaus Aehlig
  let master_names = map Node.name . filter Node.isMaster . IntMap.elems $
125 7dbe4c72 Klaus Aehlig
                     fixed_nl
126 7dbe4c72 Klaus Aehlig
  case master_names of
127 7dbe4c72 Klaus Aehlig
    [] -> maybeExit "No master node found (maybe not supported by backend)."
128 7dbe4c72 Klaus Aehlig
    [ _ ] -> return ()
129 7dbe4c72 Klaus Aehlig
    _ -> exitErr $ "Found more than one master node: " ++  show master_names
130 7dbe4c72 Klaus Aehlig
131 1a9eb17e Guido Trotter
  nlf <- setNodeStatus opts fixed_nl
132 1a9eb17e Guido Trotter
133 1a9eb17e Guido Trotter
  maybeSaveData (optSaveCluster opts) "original" "before hroller run" ini_cdata
134 1a9eb17e Guido Trotter
135 2fce67b6 Guido Trotter
  -- Find the wanted node group, if any.
136 2fce67b6 Guido Trotter
  wantedGroup <- case optGroup opts of
137 2fce67b6 Guido Trotter
    Nothing -> return Nothing
138 2fce67b6 Guido Trotter
    Just name -> case Container.findByName gl name of
139 2fce67b6 Guido Trotter
      Nothing -> exitErr "Cannot find target group."
140 2fce67b6 Guido Trotter
      Just grp -> return (Just grp)
141 2fce67b6 Guido Trotter
142 313fdabc Klaus Aehlig
  let nodes = IntMap.filter (foldl (liftA2 (&&)) (const True)
143 3409c0af Klaus Aehlig
                             [ not . Node.offline
144 004398d0 Klaus Aehlig
                             , hasTag $ optNodeTags opts
145 313fdabc Klaus Aehlig
                             , hasGroup wantedGroup ])
146 442d5aae Klaus Aehlig
              nlf
147 8d38fb72 Klaus Aehlig
      mkGraph = if optOfflineMaintenance opts
148 8d38fb72 Klaus Aehlig
                   then Node.mkNodeGraph
149 8d38fb72 Klaus Aehlig
                   else Node.mkRebootNodeGraph nlf
150 442d5aae Klaus Aehlig
151 1a9eb17e Guido Trotter
  -- TODO: fail if instances are running (with option to warn only)
152 1a9eb17e Guido Trotter
153 8d38fb72 Klaus Aehlig
  nodeGraph <- case mkGraph nodes ilf of
154 1a9eb17e Guido Trotter
                     Nothing -> exitErr "Cannot create node graph"
155 1a9eb17e Guido Trotter
                     Just g -> return g
156 1a9eb17e Guido Trotter
157 1a9eb17e Guido Trotter
  when (verbose > 2) . putStrLn $ "Node Graph: " ++ show nodeGraph
158 1a9eb17e Guido Trotter
159 1a9eb17e Guido Trotter
  let colorAlgorithms = [ ("LF", colorLF)
160 1a9eb17e Guido Trotter
                        , ("Dsatur", colorDsatur)
161 1a9eb17e Guido Trotter
                        , ("Dcolor", colorDcolor)
162 1a9eb17e Guido Trotter
                        ]
163 1a9eb17e Guido Trotter
      colorings = map (\(v,a) -> (v,(colorVertMap.a) nodeGraph)) colorAlgorithms
164 1a9eb17e Guido Trotter
      smallestColoring =
165 1a9eb17e Guido Trotter
        (snd . minimumBy (comparing (IntMap.size . snd))) colorings
166 442d5aae Klaus Aehlig
      idToNode = (`Container.find` nodes)
167 442d5aae Klaus Aehlig
      nodesRebootGroups =
168 442d5aae Klaus Aehlig
        map (map idToNode . filter (`IntMap.member` nodes)) $
169 442d5aae Klaus Aehlig
        IntMap.elems smallestColoring
170 a39779f6 Klaus Aehlig
      outputRebootGroups = masterLast .
171 a39779f6 Klaus Aehlig
                           sortBy (flip compare `on` length) $
172 a39779f6 Klaus Aehlig
                           nodesRebootGroups
173 544029d3 Guido Trotter
      outputRebootNames = map (map Node.name) outputRebootGroups
174 1a9eb17e Guido Trotter
175 1a9eb17e Guido Trotter
  when (verbose > 1) . putStrLn $ getStats colorings
176 1a9eb17e Guido Trotter
177 2207220d Klaus Aehlig
  if optOneStepOnly opts
178 2207220d Klaus Aehlig
     then do
179 2207220d Klaus Aehlig
       unless (optNoHeaders opts) $
180 2207220d Klaus Aehlig
              putStrLn "'First Reboot Group'"
181 2207220d Klaus Aehlig
       case outputRebootNames of
182 2207220d Klaus Aehlig
         [] -> return ()
183 2207220d Klaus Aehlig
         y : _ -> mapM_ putStrLn y
184 2207220d Klaus Aehlig
     else do
185 2207220d Klaus Aehlig
       unless (optNoHeaders opts) $
186 2207220d Klaus Aehlig
              putStrLn "'Node Reboot Groups'"
187 2207220d Klaus Aehlig
       mapM_ (putStrLn . commaJoin) outputRebootNames