Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hroller.hs @ 89363f98

History | View | Annotate | Download (6.9 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
    , oSkipNonRedundant
69
    , oForce
70
    , oOneStepOnly
71
    ]
72

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

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

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

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

    
105
-- | From a cluster configuration, get the list of non-redundant instances
106
-- of a node.
107
nonRedundant :: (Node.List, Instance.List) -> Ndx -> [Idx]
108
nonRedundant (nl, il) ndx =
109
  filter (not . Instance.hasSecondary . flip Container.find  il) $
110
  Node.pList (Container.find ndx nl)
111

    
112
-- | Within a cluster configuration, decide if the node hosts non-redundant
113
-- Instances.
114
noNonRedundant :: (Node.List, Instance.List) -> Node.Node -> Bool
115
noNonRedundant conf = null . nonRedundant conf . Node.idx
116

    
117
-- | Put the master node last.
118
-- Reorder a list of lists of nodes such that the master node (if present)
119
-- is the last node of the last group.
120
masterLast :: [[Node.Node]] -> [[Node.Node]]
121
masterLast rebootgroups =
122
  map (uncurry (++)) . uncurry (++) . partition (null . snd) $
123
  map (partition (not . Node.isMaster)) rebootgroups
124

    
125
-- | Main function.
126
main :: Options -> [String] -> IO ()
127
main opts args = do
128
  unless (null args) $ exitErr "This program doesn't take any arguments."
129

    
130
  let verbose = optVerbose opts
131
      maybeExit = if optForce opts then warn else exitErr
132

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

    
137
  let master_names = map Node.name . filter Node.isMaster . IntMap.elems $
138
                     fixed_nl
139
  case master_names of
140
    [] -> maybeExit "No master node found (maybe not supported by backend)."
141
    [ _ ] -> return ()
142
    _ -> exitErr $ "Found more than one master node: " ++  show master_names
143

    
144
  nlf <- setNodeStatus opts fixed_nl
145

    
146
  maybeSaveData (optSaveCluster opts) "original" "before hroller run" ini_cdata
147

    
148
  -- Find the wanted node group, if any.
149
  wantedGroup <- case optGroup opts of
150
    Nothing -> return Nothing
151
    Just name -> case Container.findByName gl name of
152
      Nothing -> exitErr "Cannot find target group."
153
      Just grp -> return (Just grp)
154

    
155
  let nodes = IntMap.filter (foldl (liftA2 (&&)) (const True)
156
                             [ not . Node.offline
157
                             , if optSkipNonRedundant opts
158
                                  then noNonRedundant (nlf, ilf)
159
                                  else const True
160
                             , hasTag $ optNodeTags opts
161
                             , hasGroup wantedGroup ])
162
              nlf
163
      mkGraph = if optOfflineMaintenance opts
164
                   then Node.mkNodeGraph
165
                   else Node.mkRebootNodeGraph nlf
166

    
167
  -- TODO: fail if instances are running (with option to warn only)
168

    
169
  nodeGraph <- case mkGraph nodes ilf of
170
                     Nothing -> exitErr "Cannot create node graph"
171
                     Just g -> return g
172

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

    
175
  let colorAlgorithms = [ ("LF", colorLF)
176
                        , ("Dsatur", colorDsatur)
177
                        , ("Dcolor", colorDcolor)
178
                        ]
179
      colorings = map (\(v,a) -> (v,(colorVertMap.a) nodeGraph)) colorAlgorithms
180
      smallestColoring =
181
        (snd . minimumBy (comparing (IntMap.size . snd))) colorings
182
      idToNode = (`Container.find` nodes)
183
      nodesRebootGroups =
184
        map (map idToNode . filter (`IntMap.member` nodes)) $
185
        IntMap.elems smallestColoring
186
      outputRebootGroups = masterLast .
187
                           sortBy (flip compare `on` length) $
188
                           nodesRebootGroups
189
      outputRebootNames = map (map Node.name) outputRebootGroups
190

    
191
  when (verbose > 1) . putStrLn $ getStats colorings
192

    
193
  if optOneStepOnly opts
194
     then do
195
       unless (optNoHeaders opts) $
196
              putStrLn "'First Reboot Group'"
197
       case outputRebootNames of
198
         [] -> return ()
199
         y : _ -> mapM_ putStrLn y
200
     else do
201
       unless (optNoHeaders opts) $
202
              putStrLn "'Node Reboot Groups'"
203
       mapM_ (putStrLn . commaJoin) outputRebootNames