Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ aa5b2f07

History | View | Annotate | Download (19.2 kB)

1 209b3711 Iustin Pop
{-| Implementation of command-line functions.
2 209b3711 Iustin Pop
3 525bfb36 Iustin Pop
This module holds the common command-line related functions for the
4 525bfb36 Iustin Pop
binaries, separated into this module since "Ganeti.HTools.Utils" is
5 525bfb36 Iustin Pop
used in many other places and this is more IO oriented.
6 209b3711 Iustin Pop
7 209b3711 Iustin Pop
-}
8 209b3711 Iustin Pop
9 e2fa2baf Iustin Pop
{-
10 e2fa2baf Iustin Pop
11 a69ff623 Iustin Pop
Copyright (C) 2009, 2010, 2011 Google Inc.
12 e2fa2baf Iustin Pop
13 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
14 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
15 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
16 e2fa2baf Iustin Pop
(at your option) any later version.
17 e2fa2baf Iustin Pop
18 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
19 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
20 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
21 e2fa2baf Iustin Pop
General Public License for more details.
22 e2fa2baf Iustin Pop
23 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
24 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
25 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
26 e2fa2baf Iustin Pop
02110-1301, USA.
27 e2fa2baf Iustin Pop
28 e2fa2baf Iustin Pop
-}
29 e2fa2baf Iustin Pop
30 209b3711 Iustin Pop
module Ganeti.HTools.CLI
31 cd08cfa4 Iustin Pop
  ( Options(..)
32 cd08cfa4 Iustin Pop
  , OptType
33 cd08cfa4 Iustin Pop
  , parseOpts
34 cd08cfa4 Iustin Pop
  , shTemplate
35 cd08cfa4 Iustin Pop
  , defaultLuxiSocket
36 cd08cfa4 Iustin Pop
  , maybePrintNodes
37 cd08cfa4 Iustin Pop
  , maybePrintInsts
38 cd08cfa4 Iustin Pop
  , maybeShowWarnings
39 cd08cfa4 Iustin Pop
  , setNodeStatus
40 cd08cfa4 Iustin Pop
  -- * The options
41 cd08cfa4 Iustin Pop
  , oDataFile
42 cd08cfa4 Iustin Pop
  , oDiskMoves
43 cd08cfa4 Iustin Pop
  , oDiskTemplate
44 cd08cfa4 Iustin Pop
  , oDynuFile
45 cd08cfa4 Iustin Pop
  , oEvacMode
46 cd08cfa4 Iustin Pop
  , oExInst
47 cd08cfa4 Iustin Pop
  , oExTags
48 cd08cfa4 Iustin Pop
  , oExecJobs
49 cd08cfa4 Iustin Pop
  , oGroup
50 cd08cfa4 Iustin Pop
  , oInstMoves
51 cd08cfa4 Iustin Pop
  , oLuxiSocket
52 cd08cfa4 Iustin Pop
  , oMachineReadable
53 cd08cfa4 Iustin Pop
  , oMaxCpu
54 cd08cfa4 Iustin Pop
  , oMaxSolLength
55 cd08cfa4 Iustin Pop
  , oMinDisk
56 cd08cfa4 Iustin Pop
  , oMinGain
57 cd08cfa4 Iustin Pop
  , oMinGainLim
58 cd08cfa4 Iustin Pop
  , oMinScore
59 cd08cfa4 Iustin Pop
  , oNoHeaders
60 cd08cfa4 Iustin Pop
  , oNodeSim
61 cd08cfa4 Iustin Pop
  , oOfflineNode
62 cd08cfa4 Iustin Pop
  , oOutputDir
63 cd08cfa4 Iustin Pop
  , oPrintCommands
64 cd08cfa4 Iustin Pop
  , oPrintInsts
65 cd08cfa4 Iustin Pop
  , oPrintNodes
66 cd08cfa4 Iustin Pop
  , oQuiet
67 cd08cfa4 Iustin Pop
  , oRapiMaster
68 cd08cfa4 Iustin Pop
  , oReplay
69 cd08cfa4 Iustin Pop
  , oSaveCluster
70 cd08cfa4 Iustin Pop
  , oSelInst
71 cd08cfa4 Iustin Pop
  , oShowHelp
72 cd08cfa4 Iustin Pop
  , oShowVer
73 294bb337 Iustin Pop
  , oStdSpec
74 cd08cfa4 Iustin Pop
  , oTieredSpec
75 cd08cfa4 Iustin Pop
  , oVerbose
76 cd08cfa4 Iustin Pop
  ) where
77 209b3711 Iustin Pop
78 cc532bdd Iustin Pop
import Control.Monad
79 e8f89bb6 Iustin Pop
import Data.Maybe (fromMaybe)
80 8e445e6d Iustin Pop
import qualified Data.Version
81 209b3711 Iustin Pop
import System.Console.GetOpt
82 209b3711 Iustin Pop
import System.IO
83 209b3711 Iustin Pop
import System.Info
84 7345b69b Iustin Pop
import System.Exit
85 5296ee23 Iustin Pop
import Text.Printf (printf, hPrintf)
86 209b3711 Iustin Pop
87 209b3711 Iustin Pop
import qualified Ganeti.HTools.Version as Version(version)
88 5296ee23 Iustin Pop
import qualified Ganeti.HTools.Container as Container
89 5296ee23 Iustin Pop
import qualified Ganeti.HTools.Node as Node
90 a69ff623 Iustin Pop
import qualified Ganeti.Constants as C
91 92e32d76 Iustin Pop
import Ganeti.HTools.Types
92 1f9066c0 Iustin Pop
import Ganeti.HTools.Utils
93 5296ee23 Iustin Pop
import Ganeti.HTools.Loader
94 fae371cc Iustin Pop
95 525bfb36 Iustin Pop
-- * Constants
96 525bfb36 Iustin Pop
97 525bfb36 Iustin Pop
-- | The default value for the luxi socket.
98 525bfb36 Iustin Pop
--
99 525bfb36 Iustin Pop
-- This is re-exported from the "Ganeti.Constants" module.
100 8e445e6d Iustin Pop
defaultLuxiSocket :: FilePath
101 a69ff623 Iustin Pop
defaultLuxiSocket = C.masterSocket
102 8e445e6d Iustin Pop
103 525bfb36 Iustin Pop
-- * Data types
104 525bfb36 Iustin Pop
105 0427285d Iustin Pop
-- | Command line options structure.
106 0427285d Iustin Pop
data Options = Options
107 cd08cfa4 Iustin Pop
  { optDataFile    :: Maybe FilePath -- ^ Path to the cluster data file
108 cd08cfa4 Iustin Pop
  , optDiskMoves   :: Bool           -- ^ Allow disk moves
109 cd08cfa4 Iustin Pop
  , optInstMoves   :: Bool           -- ^ Allow instance moves
110 9fdd3d0f Iustin Pop
  , optDiskTemplate :: Maybe DiskTemplate  -- ^ Override for the disk template
111 cd08cfa4 Iustin Pop
  , optDynuFile    :: Maybe FilePath -- ^ Optional file with dynamic use data
112 cd08cfa4 Iustin Pop
  , optEvacMode    :: Bool           -- ^ Enable evacuation mode
113 cd08cfa4 Iustin Pop
  , optExInst      :: [String]       -- ^ Instances to be excluded
114 cd08cfa4 Iustin Pop
  , optExTags      :: Maybe [String] -- ^ Tags to use for exclusion
115 cd08cfa4 Iustin Pop
  , optExecJobs    :: Bool           -- ^ Execute the commands via Luxi
116 cd08cfa4 Iustin Pop
  , optGroup       :: Maybe GroupID  -- ^ The UUID of the group to process
117 cd08cfa4 Iustin Pop
  , optSelInst     :: [String]       -- ^ Instances to be excluded
118 cd08cfa4 Iustin Pop
  , optLuxi        :: Maybe FilePath -- ^ Collect data from Luxi
119 cd08cfa4 Iustin Pop
  , optMachineReadable :: Bool       -- ^ Output machine-readable format
120 cd08cfa4 Iustin Pop
  , optMaster      :: String         -- ^ Collect data from RAPI
121 cd08cfa4 Iustin Pop
  , optMaxLength   :: Int            -- ^ Stop after this many steps
122 cd08cfa4 Iustin Pop
  , optMcpu        :: Double         -- ^ Max cpu ratio for nodes
123 cd08cfa4 Iustin Pop
  , optMdsk        :: Double         -- ^ Max disk usage ratio for nodes
124 cd08cfa4 Iustin Pop
  , optMinGain     :: Score          -- ^ Min gain we aim for in a step
125 cd08cfa4 Iustin Pop
  , optMinGainLim  :: Score          -- ^ Limit below which we apply mingain
126 cd08cfa4 Iustin Pop
  , optMinScore    :: Score          -- ^ The minimum score we aim for
127 cd08cfa4 Iustin Pop
  , optNoHeaders   :: Bool           -- ^ Do not show a header line
128 cd08cfa4 Iustin Pop
  , optNodeSim     :: [String]       -- ^ Cluster simulation mode
129 cd08cfa4 Iustin Pop
  , optOffline     :: [String]       -- ^ Names of offline nodes
130 cd08cfa4 Iustin Pop
  , optOutPath     :: FilePath       -- ^ Path to the output directory
131 cd08cfa4 Iustin Pop
  , optSaveCluster :: Maybe FilePath -- ^ Save cluster state to this file
132 cd08cfa4 Iustin Pop
  , optShowCmds    :: Maybe FilePath -- ^ Whether to show the command list
133 cd08cfa4 Iustin Pop
  , optShowHelp    :: Bool           -- ^ Just show the help
134 cd08cfa4 Iustin Pop
  , optShowInsts   :: Bool           -- ^ Whether to show the instance map
135 cd08cfa4 Iustin Pop
  , optShowNodes   :: Maybe [String] -- ^ Whether to show node status
136 cd08cfa4 Iustin Pop
  , optShowVer     :: Bool           -- ^ Just show the program version
137 be468da0 Iustin Pop
  , optStdSpec     :: Maybe RSpec    -- ^ Requested standard specs
138 cd08cfa4 Iustin Pop
  , optTieredSpec  :: Maybe RSpec    -- ^ Requested specs for tiered mode
139 cd08cfa4 Iustin Pop
  , optReplay      :: Maybe String   -- ^ Unittests: RNG state
140 cd08cfa4 Iustin Pop
  , optVerbose     :: Int            -- ^ Verbosity level
141 cd08cfa4 Iustin Pop
  } deriving Show
142 0427285d Iustin Pop
143 0427285d Iustin Pop
-- | Default values for the command line options.
144 0427285d Iustin Pop
defaultOptions :: Options
145 0427285d Iustin Pop
defaultOptions  = Options
146 cd08cfa4 Iustin Pop
  { optDataFile    = Nothing
147 cd08cfa4 Iustin Pop
  , optDiskMoves   = True
148 cd08cfa4 Iustin Pop
  , optInstMoves   = True
149 9fdd3d0f Iustin Pop
  , optDiskTemplate = Nothing
150 cd08cfa4 Iustin Pop
  , optDynuFile    = Nothing
151 cd08cfa4 Iustin Pop
  , optEvacMode    = False
152 cd08cfa4 Iustin Pop
  , optExInst      = []
153 cd08cfa4 Iustin Pop
  , optExTags      = Nothing
154 cd08cfa4 Iustin Pop
  , optExecJobs    = False
155 cd08cfa4 Iustin Pop
  , optGroup       = Nothing
156 cd08cfa4 Iustin Pop
  , optSelInst     = []
157 cd08cfa4 Iustin Pop
  , optLuxi        = Nothing
158 cd08cfa4 Iustin Pop
  , optMachineReadable = False
159 cd08cfa4 Iustin Pop
  , optMaster      = ""
160 cd08cfa4 Iustin Pop
  , optMaxLength   = -1
161 cd08cfa4 Iustin Pop
  , optMcpu        = defVcpuRatio
162 cd08cfa4 Iustin Pop
  , optMdsk        = defReservedDiskRatio
163 cd08cfa4 Iustin Pop
  , optMinGain     = 1e-2
164 cd08cfa4 Iustin Pop
  , optMinGainLim  = 1e-1
165 cd08cfa4 Iustin Pop
  , optMinScore    = 1e-9
166 cd08cfa4 Iustin Pop
  , optNoHeaders   = False
167 cd08cfa4 Iustin Pop
  , optNodeSim     = []
168 cd08cfa4 Iustin Pop
  , optOffline     = []
169 cd08cfa4 Iustin Pop
  , optOutPath     = "."
170 cd08cfa4 Iustin Pop
  , optSaveCluster = Nothing
171 cd08cfa4 Iustin Pop
  , optShowCmds    = Nothing
172 cd08cfa4 Iustin Pop
  , optShowHelp    = False
173 cd08cfa4 Iustin Pop
  , optShowInsts   = False
174 cd08cfa4 Iustin Pop
  , optShowNodes   = Nothing
175 cd08cfa4 Iustin Pop
  , optShowVer     = False
176 be468da0 Iustin Pop
  , optStdSpec     = Nothing
177 cd08cfa4 Iustin Pop
  , optTieredSpec  = Nothing
178 cd08cfa4 Iustin Pop
  , optReplay      = Nothing
179 cd08cfa4 Iustin Pop
  , optVerbose     = 1
180 cd08cfa4 Iustin Pop
  }
181 0427285d Iustin Pop
182 525bfb36 Iustin Pop
-- | Abrreviation for the option type.
183 2f567ac0 Iustin Pop
type OptType = OptDescr (Options -> Result Options)
184 0427285d Iustin Pop
185 7da760ca Iustin Pop
-- * Helper functions
186 7da760ca Iustin Pop
187 7da760ca Iustin Pop
parseISpecString :: String -> String -> Result RSpec
188 7da760ca Iustin Pop
parseISpecString descr inp = do
189 7da760ca Iustin Pop
  let sp = sepSplit ',' inp
190 7da760ca Iustin Pop
  prs <- mapM (\(fn, val) -> fn val) $
191 7da760ca Iustin Pop
         zip [ annotateResult (descr ++ " specs memory") . parseUnit
192 7da760ca Iustin Pop
             , annotateResult (descr ++ " specs disk") . parseUnit
193 7da760ca Iustin Pop
             , tryRead (descr ++ " specs cpus")
194 7da760ca Iustin Pop
             ] sp
195 7da760ca Iustin Pop
  case prs of
196 7da760ca Iustin Pop
    [dsk, ram, cpu] -> return $ RSpec cpu ram dsk
197 7da760ca Iustin Pop
    _ -> Bad $ "Invalid " ++ descr ++ " specification: '" ++ inp ++
198 7da760ca Iustin Pop
         "', expected disk,ram,cpu"
199 7da760ca Iustin Pop
200 525bfb36 Iustin Pop
-- * Command line options
201 525bfb36 Iustin Pop
202 16c2369c Iustin Pop
oDataFile :: OptType
203 16c2369c Iustin Pop
oDataFile = Option "t" ["text-data"]
204 16c2369c Iustin Pop
            (ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
205 16c2369c Iustin Pop
            "the cluster data FILE"
206 0427285d Iustin Pop
207 df18fdfe Iustin Pop
oDiskMoves :: OptType
208 df18fdfe Iustin Pop
oDiskMoves = Option "" ["no-disk-moves"]
209 df18fdfe Iustin Pop
             (NoArg (\ opts -> Ok opts { optDiskMoves = False}))
210 df18fdfe Iustin Pop
             "disallow disk moves from the list of allowed instance changes,\
211 df18fdfe Iustin Pop
             \ thus allowing only the 'cheap' failover/migrate operations"
212 b2278348 Iustin Pop
213 c4bb977b Iustin Pop
oDiskTemplate :: OptType
214 c4bb977b Iustin Pop
oDiskTemplate = Option "" ["disk-template"]
215 c4bb977b Iustin Pop
                (ReqArg (\ t opts -> do
216 5f828ce4 Agata Murawska
                           dt <- diskTemplateFromRaw t
217 9fdd3d0f Iustin Pop
                           return $ opts { optDiskTemplate = Just dt })
218 9fdd3d0f Iustin Pop
                 "TEMPLATE") "select the desired disk template"
219 c4bb977b Iustin Pop
220 ddef0585 Guido Trotter
oSelInst :: OptType
221 ddef0585 Guido Trotter
oSelInst = Option "" ["select-instances"]
222 ddef0585 Guido Trotter
          (ReqArg (\ f opts -> Ok opts { optSelInst = sepSplit ',' f }) "INSTS")
223 ddef0585 Guido Trotter
          "only select given instances for any moves"
224 ddef0585 Guido Trotter
225 8fcfb767 Guido Trotter
oInstMoves :: OptType
226 8fcfb767 Guido Trotter
oInstMoves = Option "" ["no-instance-moves"]
227 8fcfb767 Guido Trotter
             (NoArg (\ opts -> Ok opts { optInstMoves = False}))
228 8fcfb767 Guido Trotter
             "disallow instance (primary node) moves from the list of allowed,\
229 8fcfb767 Guido Trotter
             \ instance changes, thus allowing only slower, but sometimes\
230 8fcfb767 Guido Trotter
             \ safer, drbd secondary changes"
231 8fcfb767 Guido Trotter
232 df18fdfe Iustin Pop
oDynuFile :: OptType
233 df18fdfe Iustin Pop
oDynuFile = Option "U" ["dynu-file"]
234 df18fdfe Iustin Pop
            (ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
235 df18fdfe Iustin Pop
            "Import dynamic utilisation data from the given FILE"
236 0427285d Iustin Pop
237 f0f21ec4 Iustin Pop
oEvacMode :: OptType
238 f0f21ec4 Iustin Pop
oEvacMode = Option "E" ["evac-mode"]
239 f0f21ec4 Iustin Pop
            (NoArg (\opts -> Ok opts { optEvacMode = True }))
240 f0f21ec4 Iustin Pop
            "enable evacuation mode, where the algorithm only moves \
241 f0f21ec4 Iustin Pop
            \ instances away from offline and drained nodes"
242 f0f21ec4 Iustin Pop
243 10f396e1 Iustin Pop
oExInst :: OptType
244 10f396e1 Iustin Pop
oExInst = Option "" ["exclude-instances"]
245 10f396e1 Iustin Pop
          (ReqArg (\ f opts -> Ok opts { optExInst = sepSplit ',' f }) "INSTS")
246 6c30ce16 Guido Trotter
          "exclude given instances from any moves"
247 10f396e1 Iustin Pop
248 df18fdfe Iustin Pop
oExTags :: OptType
249 df18fdfe Iustin Pop
oExTags = Option "" ["exclusion-tags"]
250 df18fdfe Iustin Pop
            (ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
251 df18fdfe Iustin Pop
             "TAG,...") "Enable instance exclusion based on given tag prefix"
252 0427285d Iustin Pop
253 0df5a1b4 Iustin Pop
oExecJobs :: OptType
254 0df5a1b4 Iustin Pop
oExecJobs = Option "X" ["exec"]
255 2f567ac0 Iustin Pop
             (NoArg (\ opts -> Ok opts { optExecJobs = True}))
256 0df5a1b4 Iustin Pop
             "execute the suggested moves via Luxi (only available when using\
257 71e635f3 René Nussbaumer
             \ it for data gathering)"
258 0df5a1b4 Iustin Pop
259 a423b510 Iustin Pop
oGroup :: OptType
260 a423b510 Iustin Pop
oGroup = Option "G" ["group"]
261 a423b510 Iustin Pop
            (ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
262 a423b510 Iustin Pop
            "the ID of the group to balance"
263 a423b510 Iustin Pop
264 df18fdfe Iustin Pop
oLuxiSocket :: OptType
265 df18fdfe Iustin Pop
oLuxiSocket = Option "L" ["luxi"]
266 df18fdfe Iustin Pop
              (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
267 df18fdfe Iustin Pop
                       fromMaybe defaultLuxiSocket) "SOCKET")
268 df18fdfe Iustin Pop
              "collect data via Luxi, optionally using the given SOCKET path"
269 0427285d Iustin Pop
270 519edd9f Iustin Pop
oMachineReadable :: OptType
271 519edd9f Iustin Pop
oMachineReadable = Option "" ["machine-readable"]
272 cd08cfa4 Iustin Pop
                   (OptArg (\ f opts -> do
273 519edd9f Iustin Pop
                     flag <- parseYesNo True f
274 519edd9f Iustin Pop
                     return $ opts { optMachineReadable = flag }) "CHOICE")
275 519edd9f Iustin Pop
          "enable machine readable output (pass either 'yes' or 'no' to\
276 519edd9f Iustin Pop
          \ explicitely control the flag, or without an argument defaults to\
277 519edd9f Iustin Pop
          \ yes"
278 519edd9f Iustin Pop
279 0427285d Iustin Pop
oMaxCpu :: OptType
280 0427285d Iustin Pop
oMaxCpu = Option "" ["max-cpu"]
281 2f567ac0 Iustin Pop
          (ReqArg (\ n opts -> Ok opts { optMcpu = read n }) "RATIO")
282 f4c0b8c5 Iustin Pop
          "maximum virtual-to-physical cpu ratio for nodes (from 1\
283 f4c0b8c5 Iustin Pop
          \ upwards) [64]"
284 0427285d Iustin Pop
285 df18fdfe Iustin Pop
oMaxSolLength :: OptType
286 df18fdfe Iustin Pop
oMaxSolLength = Option "l" ["max-length"]
287 df18fdfe Iustin Pop
                (ReqArg (\ i opts -> Ok opts { optMaxLength = read i }) "N")
288 b8a2c0ab Iustin Pop
                "cap the solution at this many balancing or allocation \
289 b8a2c0ab Iustin Pop
                \ rounds (useful for very unbalanced clusters or empty \
290 b8a2c0ab Iustin Pop
                \ clusters)"
291 df18fdfe Iustin Pop
292 0427285d Iustin Pop
oMinDisk :: OptType
293 0427285d Iustin Pop
oMinDisk = Option "" ["min-disk"]
294 2f567ac0 Iustin Pop
           (ReqArg (\ n opts -> Ok opts { optMdsk = read n }) "RATIO")
295 f4c0b8c5 Iustin Pop
           "minimum free disk space for nodes (between 0 and 1) [0]"
296 0427285d Iustin Pop
297 4f807a57 Iustin Pop
oMinGain :: OptType
298 4f807a57 Iustin Pop
oMinGain = Option "g" ["min-gain"]
299 4f807a57 Iustin Pop
            (ReqArg (\ g opts -> Ok opts { optMinGain = read g }) "DELTA")
300 4f807a57 Iustin Pop
            "minimum gain to aim for in a balancing step before giving up"
301 4f807a57 Iustin Pop
302 4f807a57 Iustin Pop
oMinGainLim :: OptType
303 4f807a57 Iustin Pop
oMinGainLim = Option "" ["min-gain-limit"]
304 4f807a57 Iustin Pop
            (ReqArg (\ g opts -> Ok opts { optMinGainLim = read g }) "SCORE")
305 4f807a57 Iustin Pop
            "minimum cluster score for which we start checking the min-gain"
306 4f807a57 Iustin Pop
307 df18fdfe Iustin Pop
oMinScore :: OptType
308 df18fdfe Iustin Pop
oMinScore = Option "e" ["min-score"]
309 df18fdfe Iustin Pop
            (ReqArg (\ e opts -> Ok opts { optMinScore = read e }) "EPSILON")
310 4f807a57 Iustin Pop
            "mininum score to aim for"
311 c0501c69 Iustin Pop
312 df18fdfe Iustin Pop
oNoHeaders :: OptType
313 df18fdfe Iustin Pop
oNoHeaders = Option "" ["no-headers"]
314 df18fdfe Iustin Pop
             (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
315 df18fdfe Iustin Pop
             "do not show a header line"
316 4f83a560 Iustin Pop
317 df18fdfe Iustin Pop
oNodeSim :: OptType
318 df18fdfe Iustin Pop
oNodeSim = Option "" ["simulate"]
319 9983063b Iustin Pop
            (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
320 df18fdfe Iustin Pop
            "simulate an empty cluster, given as 'num_nodes,disk,ram,cpu'"
321 df18fdfe Iustin Pop
322 df18fdfe Iustin Pop
oOfflineNode :: OptType
323 df18fdfe Iustin Pop
oOfflineNode = Option "O" ["offline"]
324 df18fdfe Iustin Pop
               (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
325 df18fdfe Iustin Pop
               "set node as offline"
326 df18fdfe Iustin Pop
327 df18fdfe Iustin Pop
oOutputDir :: OptType
328 df18fdfe Iustin Pop
oOutputDir = Option "d" ["output-dir"]
329 df18fdfe Iustin Pop
             (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
330 df18fdfe Iustin Pop
             "directory in which to write output files"
331 df18fdfe Iustin Pop
332 df18fdfe Iustin Pop
oPrintCommands :: OptType
333 df18fdfe Iustin Pop
oPrintCommands = Option "C" ["print-commands"]
334 df18fdfe Iustin Pop
                 (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
335 df18fdfe Iustin Pop
                          fromMaybe "-")
336 df18fdfe Iustin Pop
                  "FILE")
337 df18fdfe Iustin Pop
                 "print the ganeti command list for reaching the solution,\
338 df18fdfe Iustin Pop
                 \ if an argument is passed then write the commands to a\
339 df18fdfe Iustin Pop
                 \ file named as such"
340 df18fdfe Iustin Pop
341 df18fdfe Iustin Pop
oPrintInsts :: OptType
342 df18fdfe Iustin Pop
oPrintInsts = Option "" ["print-instances"]
343 df18fdfe Iustin Pop
              (NoArg (\ opts -> Ok opts { optShowInsts = True }))
344 df18fdfe Iustin Pop
              "print the final instance map"
345 df18fdfe Iustin Pop
346 df18fdfe Iustin Pop
oPrintNodes :: OptType
347 df18fdfe Iustin Pop
oPrintNodes = Option "p" ["print-nodes"]
348 df18fdfe Iustin Pop
              (OptArg ((\ f opts ->
349 cd08cfa4 Iustin Pop
                          let (prefix, realf) = case f of
350 cd08cfa4 Iustin Pop
                                                  '+':rest -> (["+"], rest)
351 cd08cfa4 Iustin Pop
                                                  _ -> ([], f)
352 cd08cfa4 Iustin Pop
                              splitted = prefix ++ sepSplit ',' realf
353 cd08cfa4 Iustin Pop
                          in Ok opts { optShowNodes = Just splitted }) .
354 df18fdfe Iustin Pop
                       fromMaybe []) "FIELDS")
355 df18fdfe Iustin Pop
              "print the final node list"
356 df18fdfe Iustin Pop
357 df18fdfe Iustin Pop
oQuiet :: OptType
358 df18fdfe Iustin Pop
oQuiet = Option "q" ["quiet"]
359 df18fdfe Iustin Pop
         (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
360 df18fdfe Iustin Pop
         "decrease the verbosity level"
361 df18fdfe Iustin Pop
362 df18fdfe Iustin Pop
oRapiMaster :: OptType
363 df18fdfe Iustin Pop
oRapiMaster = Option "m" ["master"]
364 df18fdfe Iustin Pop
              (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
365 df18fdfe Iustin Pop
              "collect data via RAPI at the given ADDRESS"
366 df18fdfe Iustin Pop
367 02da9d07 Iustin Pop
oSaveCluster :: OptType
368 02da9d07 Iustin Pop
oSaveCluster = Option "S" ["save"]
369 02da9d07 Iustin Pop
            (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
370 02da9d07 Iustin Pop
            "Save cluster state at the end of the processing to FILE"
371 02da9d07 Iustin Pop
372 df18fdfe Iustin Pop
oShowHelp :: OptType
373 df18fdfe Iustin Pop
oShowHelp = Option "h" ["help"]
374 df18fdfe Iustin Pop
            (NoArg (\ opts -> Ok opts { optShowHelp = True}))
375 df18fdfe Iustin Pop
            "show help"
376 df18fdfe Iustin Pop
377 df18fdfe Iustin Pop
oShowVer :: OptType
378 df18fdfe Iustin Pop
oShowVer = Option "V" ["version"]
379 df18fdfe Iustin Pop
           (NoArg (\ opts -> Ok opts { optShowVer = True}))
380 df18fdfe Iustin Pop
           "show the version of the program"
381 0f15cc76 Iustin Pop
382 294bb337 Iustin Pop
oStdSpec :: OptType
383 294bb337 Iustin Pop
oStdSpec = Option "" ["standard-alloc"]
384 294bb337 Iustin Pop
             (ReqArg (\ inp opts -> do
385 294bb337 Iustin Pop
                        tspec <- parseISpecString "standard" inp
386 be468da0 Iustin Pop
                        return $ opts { optStdSpec = Just tspec } )
387 294bb337 Iustin Pop
              "STDSPEC")
388 294bb337 Iustin Pop
             "enable standard specs allocation, given as 'disk,ram,cpu'"
389 294bb337 Iustin Pop
390 1f9066c0 Iustin Pop
oTieredSpec :: OptType
391 1f9066c0 Iustin Pop
oTieredSpec = Option "" ["tiered-alloc"]
392 1f9066c0 Iustin Pop
             (ReqArg (\ inp opts -> do
393 7da760ca Iustin Pop
                        tspec <- parseISpecString "tiered" inp
394 cd08cfa4 Iustin Pop
                        return $ opts { optTieredSpec = Just tspec } )
395 1f9066c0 Iustin Pop
              "TSPEC")
396 7f4e37f0 Iustin Pop
             "enable tiered specs allocation, given as 'disk,ram,cpu'"
397 1f9066c0 Iustin Pop
398 509809db Iustin Pop
oReplay :: OptType
399 509809db Iustin Pop
oReplay = Option "" ["replay"]
400 509809db Iustin Pop
          (ReqArg (\ stat opts -> Ok opts { optReplay = Just stat } ) "STATE")
401 509809db Iustin Pop
          "Pre-seed the random number generator with STATE"
402 509809db Iustin Pop
403 df18fdfe Iustin Pop
oVerbose :: OptType
404 df18fdfe Iustin Pop
oVerbose = Option "v" ["verbose"]
405 df18fdfe Iustin Pop
           (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
406 df18fdfe Iustin Pop
           "increase the verbosity level"
407 fae371cc Iustin Pop
408 525bfb36 Iustin Pop
-- * Functions
409 525bfb36 Iustin Pop
410 519edd9f Iustin Pop
-- | Helper for parsing a yes\/no command line flag.
411 519edd9f Iustin Pop
parseYesNo :: Bool         -- ^ Default whalue (when we get a @Nothing@)
412 519edd9f Iustin Pop
           -> Maybe String -- ^ Parameter value
413 519edd9f Iustin Pop
           -> Result Bool  -- ^ Resulting boolean value
414 519edd9f Iustin Pop
parseYesNo v Nothing      = return v
415 519edd9f Iustin Pop
parseYesNo _ (Just "yes") = return True
416 519edd9f Iustin Pop
parseYesNo _ (Just "no")  = return False
417 519edd9f Iustin Pop
parseYesNo _ (Just s)     = fail $ "Invalid choice '" ++ s ++
418 519edd9f Iustin Pop
                            "', pass one of 'yes' or 'no'"
419 519edd9f Iustin Pop
420 525bfb36 Iustin Pop
-- | Usage info.
421 0427285d Iustin Pop
usageHelp :: String -> [OptType] -> String
422 9f6dcdea Iustin Pop
usageHelp progname =
423 cd08cfa4 Iustin Pop
  usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
424 cd08cfa4 Iustin Pop
             progname Version.version progname)
425 78694255 Iustin Pop
426 525bfb36 Iustin Pop
-- | Command line parser, using the 'Options' structure.
427 0427285d Iustin Pop
parseOpts :: [String]               -- ^ The command line arguments
428 0427285d Iustin Pop
          -> String                 -- ^ The program name
429 0427285d Iustin Pop
          -> [OptType]              -- ^ The supported command line options
430 0427285d Iustin Pop
          -> IO (Options, [String]) -- ^ The resulting options and leftover
431 0427285d Iustin Pop
                                    -- arguments
432 0427285d Iustin Pop
parseOpts argv progname options =
433 cd08cfa4 Iustin Pop
  case getOpt Permute options argv of
434 cd08cfa4 Iustin Pop
    (o, n, []) ->
435 cd08cfa4 Iustin Pop
      do
436 cd08cfa4 Iustin Pop
        let (pr, args) = (foldM (flip id) defaultOptions o, n)
437 3603605a Iustin Pop
        po <- case pr of
438 3603605a Iustin Pop
                Bad msg -> do
439 3603605a Iustin Pop
                  hPutStrLn stderr "Error while parsing command\
440 3603605a Iustin Pop
                                   \line arguments:"
441 3603605a Iustin Pop
                  hPutStrLn stderr msg
442 3603605a Iustin Pop
                  exitWith $ ExitFailure 1
443 3603605a Iustin Pop
                Ok val -> return val
444 cd08cfa4 Iustin Pop
        when (optShowHelp po) $ do
445 cd08cfa4 Iustin Pop
          putStr $ usageHelp progname options
446 cd08cfa4 Iustin Pop
          exitWith ExitSuccess
447 cd08cfa4 Iustin Pop
        when (optShowVer po) $ do
448 cd08cfa4 Iustin Pop
          printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
449 cd08cfa4 Iustin Pop
                 progname Version.version
450 cd08cfa4 Iustin Pop
                 compilerName (Data.Version.showVersion compilerVersion)
451 cd08cfa4 Iustin Pop
                 os arch :: IO ()
452 cd08cfa4 Iustin Pop
          exitWith ExitSuccess
453 cd08cfa4 Iustin Pop
        return (po, args)
454 cd08cfa4 Iustin Pop
    (_, _, errs) -> do
455 cd08cfa4 Iustin Pop
      hPutStrLn stderr $ "Command line error: "  ++ concat errs
456 cd08cfa4 Iustin Pop
      hPutStrLn stderr $ usageHelp progname options
457 cd08cfa4 Iustin Pop
      exitWith $ ExitFailure 2
458 209b3711 Iustin Pop
459 9188aeef Iustin Pop
-- | A shell script template for autogenerated scripts.
460 e0eb63f0 Iustin Pop
shTemplate :: String
461 e0eb63f0 Iustin Pop
shTemplate =
462 cd08cfa4 Iustin Pop
  printf "#!/bin/sh\n\n\
463 cd08cfa4 Iustin Pop
         \# Auto-generated script for executing cluster rebalancing\n\n\
464 cd08cfa4 Iustin Pop
         \# To stop, touch the file /tmp/stop-htools\n\n\
465 cd08cfa4 Iustin Pop
         \set -e\n\n\
466 cd08cfa4 Iustin Pop
         \check() {\n\
467 cd08cfa4 Iustin Pop
         \  if [ -f /tmp/stop-htools ]; then\n\
468 cd08cfa4 Iustin Pop
         \    echo 'Stop requested, exiting'\n\
469 cd08cfa4 Iustin Pop
         \    exit 0\n\
470 cd08cfa4 Iustin Pop
         \  fi\n\
471 cd08cfa4 Iustin Pop
         \}\n\n"
472 417f6b50 Iustin Pop
473 417f6b50 Iustin Pop
-- | Optionally print the node list.
474 417f6b50 Iustin Pop
maybePrintNodes :: Maybe [String]       -- ^ The field list
475 417f6b50 Iustin Pop
                -> String               -- ^ Informational message
476 417f6b50 Iustin Pop
                -> ([String] -> String) -- ^ Function to generate the listing
477 417f6b50 Iustin Pop
                -> IO ()
478 417f6b50 Iustin Pop
maybePrintNodes Nothing _ _ = return ()
479 417f6b50 Iustin Pop
maybePrintNodes (Just fields) msg fn = do
480 417f6b50 Iustin Pop
  hPutStrLn stderr ""
481 417f6b50 Iustin Pop
  hPutStrLn stderr (msg ++ " status:")
482 417f6b50 Iustin Pop
  hPutStrLn stderr $ fn fields
483 33e44f0c Iustin Pop
484 33e44f0c Iustin Pop
485 33e44f0c Iustin Pop
-- | Optionally print the instance list.
486 33e44f0c Iustin Pop
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
487 33e44f0c Iustin Pop
                -> String -- ^ Type of the instance map (e.g. initial)
488 33e44f0c Iustin Pop
                -> String -- ^ The instance data
489 33e44f0c Iustin Pop
                -> IO ()
490 33e44f0c Iustin Pop
maybePrintInsts do_print msg instdata =
491 33e44f0c Iustin Pop
  when do_print $ do
492 33e44f0c Iustin Pop
    hPutStrLn stderr ""
493 33e44f0c Iustin Pop
    hPutStrLn stderr $ msg ++ " instance map:"
494 33e44f0c Iustin Pop
    hPutStr stderr instdata
495 8cd36391 Iustin Pop
496 8cd36391 Iustin Pop
-- | Function to display warning messages from parsing the cluster
497 8cd36391 Iustin Pop
-- state.
498 8cd36391 Iustin Pop
maybeShowWarnings :: [String] -- ^ The warning messages
499 8cd36391 Iustin Pop
                  -> IO ()
500 8cd36391 Iustin Pop
maybeShowWarnings fix_msgs =
501 8cd36391 Iustin Pop
  unless (null fix_msgs) $ do
502 8cd36391 Iustin Pop
    hPutStrLn stderr "Warning: cluster has inconsistent data:"
503 8cd36391 Iustin Pop
    hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
504 5296ee23 Iustin Pop
505 5296ee23 Iustin Pop
-- | Set node properties based on command line options.
506 5296ee23 Iustin Pop
setNodeStatus :: Options -> Node.List -> IO Node.List
507 5296ee23 Iustin Pop
setNodeStatus opts fixed_nl = do
508 5296ee23 Iustin Pop
  let offline_passed = optOffline opts
509 5296ee23 Iustin Pop
      all_nodes = Container.elems fixed_nl
510 5296ee23 Iustin Pop
      offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
511 5296ee23 Iustin Pop
      offline_wrong = filter (not . goodLookupResult) offline_lkp
512 5296ee23 Iustin Pop
      offline_names = map lrContent offline_lkp
513 5296ee23 Iustin Pop
      offline_indices = map Node.idx $
514 5296ee23 Iustin Pop
                        filter (\n -> Node.name n `elem` offline_names)
515 5296ee23 Iustin Pop
                               all_nodes
516 5296ee23 Iustin Pop
      m_cpu = optMcpu opts
517 5296ee23 Iustin Pop
      m_dsk = optMdsk opts
518 5296ee23 Iustin Pop
519 3603605a Iustin Pop
  unless (null offline_wrong) $ do
520 5296ee23 Iustin Pop
         hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
521 5296ee23 Iustin Pop
                     (commaJoin (map lrContent offline_wrong)) :: IO ()
522 5296ee23 Iustin Pop
         exitWith $ ExitFailure 1
523 5296ee23 Iustin Pop
524 5296ee23 Iustin Pop
  let nm = Container.map (\n -> if Node.idx n `elem` offline_indices
525 5296ee23 Iustin Pop
                                then Node.setOffline n True
526 5296ee23 Iustin Pop
                                else n) fixed_nl
527 5296ee23 Iustin Pop
      nlf = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
528 5296ee23 Iustin Pop
            nm
529 5296ee23 Iustin Pop
  return nlf