Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (6.2 kB)

1
{-| Cluster rolling maintenance helper.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2012 Google Inc.
8

    
9
This program is free software; you can redistribute it and/or modify
10
it under the terms of the GNU General Public License as published by
11
the Free Software Foundation; either version 2 of the License, or
12
(at your option) any later version.
13

    
14
This program is distributed in the hope that it will be useful, but
15
WITHOUT ANY WARRANTY; without even the implied warranty of
16
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17
General Public License for more details.
18

    
19
You should have received a copy of the GNU General Public License
20
along with this program; if not, write to the Free Software
21
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22
02110-1301, USA.
23

    
24
-}
25

    
26
module Ganeti.HTools.Program.Hroller
27
  ( main
28
  , options
29
  , arguments
30
  ) where
31

    
32
import Control.Applicative
33
import Control.Monad
34
import Data.Function
35
import Data.List
36
import Data.Ord
37

    
38
import qualified Data.IntMap as IntMap
39

    
40
import qualified Ganeti.HTools.Container as Container
41
import qualified Ganeti.HTools.Node as Node
42
import qualified Ganeti.HTools.Group as Group
43

    
44
import Ganeti.Common
45
import Ganeti.HTools.CLI
46
import Ganeti.HTools.ExtLoader
47
import Ganeti.HTools.Graph
48
import Ganeti.HTools.Loader
49
import Ganeti.Utils
50

    
51
-- | Options list and functions.
52
options :: IO [OptType]
53
options = do
54
  luxi <- oLuxiSocket
55
  return
56
    [ luxi
57
    , oRapiMaster
58
    , oDataFile
59
    , oIAllocSrc
60
    , oOfflineNode
61
    , oOfflineMaintenance
62
    , oVerbose
63
    , oQuiet
64
    , oNoHeaders
65
    , oNodeTags
66
    , oSaveCluster
67
    , oGroup
68
    , oForce
69
    , oOneStepOnly
70
    ]
71

    
72
-- | The list of arguments supported by the program.
73
arguments :: [ArgCompletion]
74
arguments = []
75

    
76
-- | Gather statistics for the coloring algorithms.
77
-- Returns a string with a summary on how each algorithm has performed,
78
-- in order of non-decreasing effectiveness, and whether it tied or lost
79
-- with the previous one.
80
getStats :: [(String, ColorVertMap)] -> String
81
getStats colorings = snd . foldr helper (0,"") $ algBySize colorings
82
    where algostat (algo, cmap) = algo ++ ": " ++ size cmap ++ grpsizes cmap
83
          size cmap = show (IntMap.size cmap) ++ " "
84
          grpsizes cmap =
85
            "(" ++ commaJoin (map (show.length) (IntMap.elems cmap)) ++ ")"
86
          algBySize = sortBy (flip (comparing (IntMap.size.snd)))
87
          helper :: (String, ColorVertMap) -> (Int, String) -> (Int, String)
88
          helper el (0, _) = ((IntMap.size.snd) el, algostat el)
89
          helper el (old, str)
90
            | old == elsize = (elsize, str ++ " TIE " ++ algostat el)
91
            | otherwise = (elsize, str ++ " LOOSE " ++ algostat el)
92
              where elsize = (IntMap.size.snd) el
93

    
94
-- | Predicate of belonging to a given group restriction.
95
hasGroup :: Maybe Group.Group -> Node.Node -> Bool
96
hasGroup Nothing _ = True
97
hasGroup (Just grp) node = Node.group node == Group.idx grp
98

    
99
-- | Predicate of having at least one tag in a given set.
100
hasTag :: Maybe [String] -> Node.Node -> Bool
101
hasTag Nothing _ = True
102
hasTag (Just tags) node = not . null $ Node.nTags node `intersect` tags
103

    
104
-- | Put the master node last.
105
-- Reorder a list of lists of nodes such that the master node (if present)
106
-- is the last node of the last group.
107
masterLast :: [[Node.Node]] -> [[Node.Node]]
108
masterLast rebootgroups =
109
  map (uncurry (++)) . uncurry (++) . partition (null . snd) $
110
  map (partition (not . Node.isMaster)) rebootgroups
111

    
112
-- | Main function.
113
main :: Options -> [String] -> IO ()
114
main opts args = do
115
  unless (null args) $ exitErr "This program doesn't take any arguments."
116

    
117
  let verbose = optVerbose opts
118
      maybeExit = if optForce opts then warn else exitErr
119

    
120
  -- Load cluster data. The last two arguments, cluster tags and ipolicy, are
121
  -- currently not used by this tool.
122
  ini_cdata@(ClusterData gl fixed_nl ilf _ _) <- loadExternalData opts
123

    
124
  let master_names = map Node.name . filter Node.isMaster . IntMap.elems $
125
                     fixed_nl
126
  case master_names of
127
    [] -> maybeExit "No master node found (maybe not supported by backend)."
128
    [ _ ] -> return ()
129
    _ -> exitErr $ "Found more than one master node: " ++  show master_names
130

    
131
  nlf <- setNodeStatus opts fixed_nl
132

    
133
  maybeSaveData (optSaveCluster opts) "original" "before hroller run" ini_cdata
134

    
135
  -- Find the wanted node group, if any.
136
  wantedGroup <- case optGroup opts of
137
    Nothing -> return Nothing
138
    Just name -> case Container.findByName gl name of
139
      Nothing -> exitErr "Cannot find target group."
140
      Just grp -> return (Just grp)
141

    
142
  let nodes = IntMap.filter (foldl (liftA2 (&&)) (const True)
143
                             [ not . Node.offline
144
                             , hasTag $ optNodeTags opts
145
                             , hasGroup wantedGroup ])
146
              nlf
147
      mkGraph = if optOfflineMaintenance opts
148
                   then Node.mkNodeGraph
149
                   else Node.mkRebootNodeGraph nlf
150

    
151
  -- TODO: fail if instances are running (with option to warn only)
152

    
153
  nodeGraph <- case mkGraph nodes ilf of
154
                     Nothing -> exitErr "Cannot create node graph"
155
                     Just g -> return g
156

    
157
  when (verbose > 2) . putStrLn $ "Node Graph: " ++ show nodeGraph
158

    
159
  let colorAlgorithms = [ ("LF", colorLF)
160
                        , ("Dsatur", colorDsatur)
161
                        , ("Dcolor", colorDcolor)
162
                        ]
163
      colorings = map (\(v,a) -> (v,(colorVertMap.a) nodeGraph)) colorAlgorithms
164
      smallestColoring =
165
        (snd . minimumBy (comparing (IntMap.size . snd))) colorings
166
      idToNode = (`Container.find` nodes)
167
      nodesRebootGroups =
168
        map (map idToNode . filter (`IntMap.member` nodes)) $
169
        IntMap.elems smallestColoring
170
      outputRebootGroups = masterLast .
171
                           sortBy (flip compare `on` length) $
172
                           nodesRebootGroups
173
      outputRebootNames = map (map Node.name) outputRebootGroups
174

    
175
  when (verbose > 1) . putStrLn $ getStats colorings
176

    
177
  if optOneStepOnly opts
178
     then do
179
       unless (optNoHeaders opts) $
180
              putStrLn "'First Reboot Group'"
181
       case outputRebootNames of
182
         [] -> return ()
183
         y : _ -> mapM_ putStrLn y
184
     else do
185
       unless (optNoHeaders opts) $
186
              putStrLn "'Node Reboot Groups'"
187
       mapM_ (putStrLn . commaJoin) outputRebootNames
188