Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hroller.hs @ 442d5aae

History | View | Annotate | Download (5.4 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.List
35
import Data.Ord
36

    
37
import qualified Data.IntMap as IntMap
38

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

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

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

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

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

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

    
95
-- | Put the master node last.
96
-- Reorder a list of lists of nodes such that the master node (if present)
97
-- is the last node of the last group.
98
masterLast :: [[Node.Node]] -> [[Node.Node]]
99
masterLast rebootgroups =
100
  map (uncurry (++)) . uncurry (++) . partition (null . snd) $
101
  map (partition (not . Node.isMaster)) rebootgroups
102

    
103
-- | Main function.
104
main :: Options -> [String] -> IO ()
105
main opts args = do
106
  unless (null args) $ exitErr "This program doesn't take any arguments."
107

    
108
  let verbose = optVerbose opts
109
      maybeExit = if optForce opts then warn else exitErr
110

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

    
115
  let master_names = map Node.name . filter Node.isMaster . IntMap.elems $
116
                     fixed_nl
117
  case master_names of
118
    [] -> maybeExit "No master node found (maybe not supported by backend)."
119
    [ _ ] -> return ()
120
    _ -> exitErr $ "Found more than one master node: " ++  show master_names
121

    
122
  nlf <- setNodeStatus opts fixed_nl
123

    
124
  maybeSaveData (optSaveCluster opts) "original" "before hroller run" ini_cdata
125

    
126
  -- Find the wanted node group, if any.
127
  wantedGroup <- case optGroup opts of
128
    Nothing -> return Nothing
129
    Just name -> case Container.findByName gl name of
130
      Nothing -> exitErr "Cannot find target group."
131
      Just grp -> return (Just grp)
132

    
133
  let nodes = IntMap.filter
134
              (liftA2 (&&) (not . Node.offline) (hasGroup wantedGroup))
135
              nlf
136

    
137
  -- TODO: fail if instances are running (with option to warn only)
138

    
139
  nodeGraph <- case Node.mkNodeGraph nodes ilf of
140
                     Nothing -> exitErr "Cannot create node graph"
141
                     Just g -> return g
142

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

    
145
  let colorAlgorithms = [ ("LF", colorLF)
146
                        , ("Dsatur", colorDsatur)
147
                        , ("Dcolor", colorDcolor)
148
                        ]
149
      colorings = map (\(v,a) -> (v,(colorVertMap.a) nodeGraph)) colorAlgorithms
150
      smallestColoring =
151
        (snd . minimumBy (comparing (IntMap.size . snd))) colorings
152
      idToNode = (`Container.find` nodes)
153
      nodesRebootGroups =
154
        map (map idToNode . filter (`IntMap.member` nodes)) $
155
        IntMap.elems smallestColoring
156
      outputRebootGroups = masterLast nodesRebootGroups
157
      outputRebootNames = map (map Node.name) outputRebootGroups
158

    
159
  when (verbose > 1) . putStrLn $ getStats colorings
160

    
161
  unless (optNoHeaders opts) $
162
         putStrLn "'Node Reboot Groups'"
163
  mapM_ (putStrLn . commaJoin) outputRebootNames