Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hroller.hs @ 5b658b83

History | View | Annotate | Download (5.2 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
    ]
65

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

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

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

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

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

    
114
  let verbose = optVerbose opts
115

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

    
120
  nlf <- setNodeStatus opts fixed_nl
121

    
122
  maybeSaveData (optSaveCluster opts) "original" "before hroller run" ini_cdata
123

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

    
131
  -- TODO: fail if instances are running (with option to warn only)
132

    
133
  nodeGraph <- case Node.mkNodeGraph nlf ilf of
134
                     Nothing -> exitErr "Cannot create node graph"
135
                     Just g -> return g
136

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

    
139
  let colorAlgorithms = [ ("LF", colorLF)
140
                        , ("Dsatur", colorDsatur)
141
                        , ("Dcolor", colorDcolor)
142
                        ]
143
      colorings = map (\(v,a) -> (v,(colorVertMap.a) nodeGraph)) colorAlgorithms
144
      smallestColoring =
145
        (snd . minimumBy (comparing (IntMap.size . snd))) colorings
146
      idToNode = (`Container.find` nlf)
147
      nodesRebootGroups = map (map idToNode) $ IntMap.elems smallestColoring
148
      outputRebootGroups = masterLast $
149
                           filterOutput wantedGroup nodesRebootGroups
150
      outputRebootNames = map (map Node.name) outputRebootGroups
151

    
152
  when (verbose > 1) . putStrLn $ getStats colorings
153

    
154
  unless (optNoHeaders opts) $
155
         putStrLn "'Node Reboot Groups'"
156
  mapM_ (putStrLn . commaJoin) outputRebootNames