Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / Program / Hroller.hs @ 313fdabc

History | View | Annotate | Download (5.7 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
    , oNodeTags
64
    , oSaveCluster
65
    , oGroup
66
    , oForce
67
    ]
68

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

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

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

    
96
-- | Predicate of having at least one tag in a given set.
97
hasTag :: Maybe [String] -> Node.Node -> Bool
98
hasTag Nothing _ = True
99
hasTag (Just tags) node = not . null $ Node.nTags node `intersect` tags
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
      maybeExit = if optForce opts then warn else exitErr
116

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

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

    
128
  nlf <- setNodeStatus opts fixed_nl
129

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

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

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

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

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

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

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

    
167
  when (verbose > 1) . putStrLn $ getStats colorings
168

    
169
  unless (optNoHeaders opts) $
170
         putStrLn "'Node Reboot Groups'"
171
  mapM_ (putStrLn . commaJoin) outputRebootNames