Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (5.8 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
    ]
69

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

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

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

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

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

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

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

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

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

    
129
  nlf <- setNodeStatus opts fixed_nl
130

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

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

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

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

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

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

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

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

    
172
  unless (optNoHeaders opts) $
173
         putStrLn "'Node Reboot Groups'"
174
  mapM_ (putStrLn . commaJoin) outputRebootNames