Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hroller.hs @ 7dbe4c72

History | View | Annotate | Download (5.6 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.Monad
33
import Data.List
34
import Data.Ord
35

    
36
import qualified Data.IntMap as IntMap
37

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

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

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

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

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

    
89
-- | Filter the output list.
90
-- Only online nodes are shown, optionally belonging to a particular target
91
-- nodegroup.  Output groups which are empty after being filtered are removed
92
-- as well.
93
filterOutput :: Maybe Group.Group -> [[Node.Node]] -> [[Node.Node]]
94
filterOutput g l =
95
  let onlineOnly = filter (not . Node.offline)
96
      hasGroup grp node = Node.group node == Group.idx grp
97
      byGroupOnly Nothing xs = xs
98
      byGroupOnly (Just grp) xs = filter (hasGroup grp) xs
99
      nonNullOnly = filter (not . null)
100
  in nonNullOnly (map (onlineOnly . byGroupOnly g) l)
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
  -- TODO: fail if instances are running (with option to warn only)
141

    
142
  nodeGraph <- case Node.mkNodeGraph nlf ilf of
143
                     Nothing -> exitErr "Cannot create node graph"
144
                     Just g -> return g
145

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

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

    
161
  when (verbose > 1) . putStrLn $ getStats colorings
162

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