Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hroller.hs @ 2207220d

History | View | Annotate | Download (6.1 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
    , oVerbose
62
    , oQuiet
63
    , oNoHeaders
64
    , oNodeTags
65
    , oSaveCluster
66
    , oGroup
67
    , oForce
68
    , oOneStepOnly
69
    ]
70

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

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

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

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

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

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

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

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

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

    
130
  nlf <- setNodeStatus opts fixed_nl
131

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

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

    
141
  let nodes = IntMap.filter (foldl (liftA2 (&&)) (const True)
142
                             [ not . Node.offline 
143
                             , hasTag $ optNodeTags opts
144
                             , hasGroup wantedGroup ])
145
              nlf
146

    
147
  -- TODO: fail if instances are running (with option to warn only)
148

    
149
  nodeGraph <- case Node.mkNodeGraph nodes ilf of
150
                     Nothing -> exitErr "Cannot create node graph"
151
                     Just g -> return g
152

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

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

    
171
  when (verbose > 1) . putStrLn $ getStats colorings
172

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