Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (19.3 kB)

1
{-| Implementation of command-line functions.
2

    
3
This module holds the common command-line related functions for the
4
binaries, separated into this module since "Ganeti.HTools.Utils" is
5
used in many other places and this is more IO oriented.
6

    
7
-}
8

    
9
{-
10

    
11
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
12

    
13
This program is free software; you can redistribute it and/or modify
14
it under the terms of the GNU General Public License as published by
15
the Free Software Foundation; either version 2 of the License, or
16
(at your option) any later version.
17

    
18
This program is distributed in the hope that it will be useful, but
19
WITHOUT ANY WARRANTY; without even the implied warranty of
20
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
21
General Public License for more details.
22

    
23
You should have received a copy of the GNU General Public License
24
along with this program; if not, write to the Free Software
25
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
26
02110-1301, USA.
27

    
28
-}
29

    
30
module Ganeti.HTools.CLI
31
  ( Options(..)
32
  , OptType
33
  , parseOpts
34
  , parseYesNo
35
  , parseISpecString
36
  , shTemplate
37
  , defaultLuxiSocket
38
  , maybePrintNodes
39
  , maybePrintInsts
40
  , maybeShowWarnings
41
  , setNodeStatus
42
  -- * The options
43
  , oDataFile
44
  , oDiskMoves
45
  , oDiskTemplate
46
  , oDynuFile
47
  , oEvacMode
48
  , oExInst
49
  , oExTags
50
  , oExecJobs
51
  , oGroup
52
  , oInstMoves
53
  , oLuxiSocket
54
  , oMachineReadable
55
  , oMaxCpu
56
  , oMaxSolLength
57
  , oMinDisk
58
  , oMinGain
59
  , oMinGainLim
60
  , oMinScore
61
  , oNoHeaders
62
  , oNodeSim
63
  , oOfflineNode
64
  , oOutputDir
65
  , oPrintCommands
66
  , oPrintInsts
67
  , oPrintNodes
68
  , oQuiet
69
  , oRapiMaster
70
  , oReplay
71
  , oSaveCluster
72
  , oSelInst
73
  , oShowHelp
74
  , oShowVer
75
  , oStdSpec
76
  , oTieredSpec
77
  , oVerbose
78
  ) where
79

    
80
import Control.Monad
81
import Data.Maybe (fromMaybe)
82
import qualified Data.Version
83
import System.Console.GetOpt
84
import System.IO
85
import System.Info
86
import System.Exit
87
import Text.Printf (printf, hPrintf)
88

    
89
import qualified Ganeti.HTools.Version as Version(version)
90
import qualified Ganeti.HTools.Container as Container
91
import qualified Ganeti.HTools.Node as Node
92
import qualified Ganeti.Constants as C
93
import Ganeti.HTools.Types
94
import Ganeti.HTools.Utils
95
import Ganeti.HTools.Loader
96

    
97
-- * Constants
98

    
99
-- | The default value for the luxi socket.
100
--
101
-- This is re-exported from the "Ganeti.Constants" module.
102
defaultLuxiSocket :: FilePath
103
defaultLuxiSocket = C.masterSocket
104

    
105
-- * Data types
106

    
107
-- | Command line options structure.
108
data Options = Options
109
  { optDataFile    :: Maybe FilePath -- ^ Path to the cluster data file
110
  , optDiskMoves   :: Bool           -- ^ Allow disk moves
111
  , optInstMoves   :: Bool           -- ^ Allow instance moves
112
  , optDiskTemplate :: Maybe DiskTemplate  -- ^ Override for the disk template
113
  , optDynuFile    :: Maybe FilePath -- ^ Optional file with dynamic use data
114
  , optEvacMode    :: Bool           -- ^ Enable evacuation mode
115
  , optExInst      :: [String]       -- ^ Instances to be excluded
116
  , optExTags      :: Maybe [String] -- ^ Tags to use for exclusion
117
  , optExecJobs    :: Bool           -- ^ Execute the commands via Luxi
118
  , optGroup       :: Maybe GroupID  -- ^ The UUID of the group to process
119
  , optSelInst     :: [String]       -- ^ Instances to be excluded
120
  , optLuxi        :: Maybe FilePath -- ^ Collect data from Luxi
121
  , optMachineReadable :: Bool       -- ^ Output machine-readable format
122
  , optMaster      :: String         -- ^ Collect data from RAPI
123
  , optMaxLength   :: Int            -- ^ Stop after this many steps
124
  , optMcpu        :: Double         -- ^ Max cpu ratio for nodes
125
  , optMdsk        :: Double         -- ^ Max disk usage ratio for nodes
126
  , optMinGain     :: Score          -- ^ Min gain we aim for in a step
127
  , optMinGainLim  :: Score          -- ^ Limit below which we apply mingain
128
  , optMinScore    :: Score          -- ^ The minimum score we aim for
129
  , optNoHeaders   :: Bool           -- ^ Do not show a header line
130
  , optNodeSim     :: [String]       -- ^ Cluster simulation mode
131
  , optOffline     :: [String]       -- ^ Names of offline nodes
132
  , optOutPath     :: FilePath       -- ^ Path to the output directory
133
  , optSaveCluster :: Maybe FilePath -- ^ Save cluster state to this file
134
  , optShowCmds    :: Maybe FilePath -- ^ Whether to show the command list
135
  , optShowHelp    :: Bool           -- ^ Just show the help
136
  , optShowInsts   :: Bool           -- ^ Whether to show the instance map
137
  , optShowNodes   :: Maybe [String] -- ^ Whether to show node status
138
  , optShowVer     :: Bool           -- ^ Just show the program version
139
  , optStdSpec     :: Maybe RSpec    -- ^ Requested standard specs
140
  , optTieredSpec  :: Maybe RSpec    -- ^ Requested specs for tiered mode
141
  , optReplay      :: Maybe String   -- ^ Unittests: RNG state
142
  , optVerbose     :: Int            -- ^ Verbosity level
143
  } deriving Show
144

    
145
-- | Default values for the command line options.
146
defaultOptions :: Options
147
defaultOptions  = Options
148
  { optDataFile    = Nothing
149
  , optDiskMoves   = True
150
  , optInstMoves   = True
151
  , optDiskTemplate = Nothing
152
  , optDynuFile    = Nothing
153
  , optEvacMode    = False
154
  , optExInst      = []
155
  , optExTags      = Nothing
156
  , optExecJobs    = False
157
  , optGroup       = Nothing
158
  , optSelInst     = []
159
  , optLuxi        = Nothing
160
  , optMachineReadable = False
161
  , optMaster      = ""
162
  , optMaxLength   = -1
163
  , optMcpu        = defVcpuRatio
164
  , optMdsk        = defReservedDiskRatio
165
  , optMinGain     = 1e-2
166
  , optMinGainLim  = 1e-1
167
  , optMinScore    = 1e-9
168
  , optNoHeaders   = False
169
  , optNodeSim     = []
170
  , optOffline     = []
171
  , optOutPath     = "."
172
  , optSaveCluster = Nothing
173
  , optShowCmds    = Nothing
174
  , optShowHelp    = False
175
  , optShowInsts   = False
176
  , optShowNodes   = Nothing
177
  , optShowVer     = False
178
  , optStdSpec     = Nothing
179
  , optTieredSpec  = Nothing
180
  , optReplay      = Nothing
181
  , optVerbose     = 1
182
  }
183

    
184
-- | Abrreviation for the option type.
185
type OptType = OptDescr (Options -> Result Options)
186

    
187
-- * Helper functions
188

    
189
parseISpecString :: String -> String -> Result RSpec
190
parseISpecString descr inp = do
191
  let sp = sepSplit ',' inp
192
      err = Bad ("Invalid " ++ descr ++ " specification: '" ++ inp ++
193
                 "', expected disk,ram,cpu")
194
  when (length sp /= 3) err
195
  prs <- mapM (\(fn, val) -> fn val) $
196
         zip [ annotateResult (descr ++ " specs disk") . parseUnit
197
             , annotateResult (descr ++ " specs memory") . parseUnit
198
             , tryRead (descr ++ " specs cpus")
199
             ] sp
200
  case prs of
201
    [dsk, ram, cpu] -> return $ RSpec cpu ram dsk
202
    _ -> err
203

    
204
-- * Command line options
205

    
206
oDataFile :: OptType
207
oDataFile = Option "t" ["text-data"]
208
            (ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
209
            "the cluster data FILE"
210

    
211
oDiskMoves :: OptType
212
oDiskMoves = Option "" ["no-disk-moves"]
213
             (NoArg (\ opts -> Ok opts { optDiskMoves = False}))
214
             "disallow disk moves from the list of allowed instance changes,\
215
             \ thus allowing only the 'cheap' failover/migrate operations"
216

    
217
oDiskTemplate :: OptType
218
oDiskTemplate = Option "" ["disk-template"]
219
                (ReqArg (\ t opts -> do
220
                           dt <- diskTemplateFromRaw t
221
                           return $ opts { optDiskTemplate = Just dt })
222
                 "TEMPLATE") "select the desired disk template"
223

    
224
oSelInst :: OptType
225
oSelInst = Option "" ["select-instances"]
226
          (ReqArg (\ f opts -> Ok opts { optSelInst = sepSplit ',' f }) "INSTS")
227
          "only select given instances for any moves"
228

    
229
oInstMoves :: OptType
230
oInstMoves = Option "" ["no-instance-moves"]
231
             (NoArg (\ opts -> Ok opts { optInstMoves = False}))
232
             "disallow instance (primary node) moves from the list of allowed,\
233
             \ instance changes, thus allowing only slower, but sometimes\
234
             \ safer, drbd secondary changes"
235

    
236
oDynuFile :: OptType
237
oDynuFile = Option "U" ["dynu-file"]
238
            (ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
239
            "Import dynamic utilisation data from the given FILE"
240

    
241
oEvacMode :: OptType
242
oEvacMode = Option "E" ["evac-mode"]
243
            (NoArg (\opts -> Ok opts { optEvacMode = True }))
244
            "enable evacuation mode, where the algorithm only moves \
245
            \ instances away from offline and drained nodes"
246

    
247
oExInst :: OptType
248
oExInst = Option "" ["exclude-instances"]
249
          (ReqArg (\ f opts -> Ok opts { optExInst = sepSplit ',' f }) "INSTS")
250
          "exclude given instances from any moves"
251

    
252
oExTags :: OptType
253
oExTags = Option "" ["exclusion-tags"]
254
            (ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
255
             "TAG,...") "Enable instance exclusion based on given tag prefix"
256

    
257
oExecJobs :: OptType
258
oExecJobs = Option "X" ["exec"]
259
             (NoArg (\ opts -> Ok opts { optExecJobs = True}))
260
             "execute the suggested moves via Luxi (only available when using\
261
             \ it for data gathering)"
262

    
263
oGroup :: OptType
264
oGroup = Option "G" ["group"]
265
            (ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
266
            "the ID of the group to balance"
267

    
268
oLuxiSocket :: OptType
269
oLuxiSocket = Option "L" ["luxi"]
270
              (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
271
                       fromMaybe defaultLuxiSocket) "SOCKET")
272
              "collect data via Luxi, optionally using the given SOCKET path"
273

    
274
oMachineReadable :: OptType
275
oMachineReadable = Option "" ["machine-readable"]
276
                   (OptArg (\ f opts -> do
277
                     flag <- parseYesNo True f
278
                     return $ opts { optMachineReadable = flag }) "CHOICE")
279
          "enable machine readable output (pass either 'yes' or 'no' to\
280
          \ explicitely control the flag, or without an argument defaults to\
281
          \ yes"
282

    
283
oMaxCpu :: OptType
284
oMaxCpu = Option "" ["max-cpu"]
285
          (ReqArg (\ n opts -> Ok opts { optMcpu = read n }) "RATIO")
286
          "maximum virtual-to-physical cpu ratio for nodes (from 1\
287
          \ upwards) [64]"
288

    
289
oMaxSolLength :: OptType
290
oMaxSolLength = Option "l" ["max-length"]
291
                (ReqArg (\ i opts -> Ok opts { optMaxLength = read i }) "N")
292
                "cap the solution at this many balancing or allocation \
293
                \ rounds (useful for very unbalanced clusters or empty \
294
                \ clusters)"
295

    
296
oMinDisk :: OptType
297
oMinDisk = Option "" ["min-disk"]
298
           (ReqArg (\ n opts -> Ok opts { optMdsk = read n }) "RATIO")
299
           "minimum free disk space for nodes (between 0 and 1) [0]"
300

    
301
oMinGain :: OptType
302
oMinGain = Option "g" ["min-gain"]
303
            (ReqArg (\ g opts -> Ok opts { optMinGain = read g }) "DELTA")
304
            "minimum gain to aim for in a balancing step before giving up"
305

    
306
oMinGainLim :: OptType
307
oMinGainLim = Option "" ["min-gain-limit"]
308
            (ReqArg (\ g opts -> Ok opts { optMinGainLim = read g }) "SCORE")
309
            "minimum cluster score for which we start checking the min-gain"
310

    
311
oMinScore :: OptType
312
oMinScore = Option "e" ["min-score"]
313
            (ReqArg (\ e opts -> Ok opts { optMinScore = read e }) "EPSILON")
314
            "mininum score to aim for"
315

    
316
oNoHeaders :: OptType
317
oNoHeaders = Option "" ["no-headers"]
318
             (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
319
             "do not show a header line"
320

    
321
oNodeSim :: OptType
322
oNodeSim = Option "" ["simulate"]
323
            (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
324
            "simulate an empty cluster, given as 'num_nodes,disk,ram,cpu'"
325

    
326
oOfflineNode :: OptType
327
oOfflineNode = Option "O" ["offline"]
328
               (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
329
               "set node as offline"
330

    
331
oOutputDir :: OptType
332
oOutputDir = Option "d" ["output-dir"]
333
             (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
334
             "directory in which to write output files"
335

    
336
oPrintCommands :: OptType
337
oPrintCommands = Option "C" ["print-commands"]
338
                 (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
339
                          fromMaybe "-")
340
                  "FILE")
341
                 "print the ganeti command list for reaching the solution,\
342
                 \ if an argument is passed then write the commands to a\
343
                 \ file named as such"
344

    
345
oPrintInsts :: OptType
346
oPrintInsts = Option "" ["print-instances"]
347
              (NoArg (\ opts -> Ok opts { optShowInsts = True }))
348
              "print the final instance map"
349

    
350
oPrintNodes :: OptType
351
oPrintNodes = Option "p" ["print-nodes"]
352
              (OptArg ((\ f opts ->
353
                          let (prefix, realf) = case f of
354
                                                  '+':rest -> (["+"], rest)
355
                                                  _ -> ([], f)
356
                              splitted = prefix ++ sepSplit ',' realf
357
                          in Ok opts { optShowNodes = Just splitted }) .
358
                       fromMaybe []) "FIELDS")
359
              "print the final node list"
360

    
361
oQuiet :: OptType
362
oQuiet = Option "q" ["quiet"]
363
         (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
364
         "decrease the verbosity level"
365

    
366
oRapiMaster :: OptType
367
oRapiMaster = Option "m" ["master"]
368
              (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
369
              "collect data via RAPI at the given ADDRESS"
370

    
371
oSaveCluster :: OptType
372
oSaveCluster = Option "S" ["save"]
373
            (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
374
            "Save cluster state at the end of the processing to FILE"
375

    
376
oShowHelp :: OptType
377
oShowHelp = Option "h" ["help"]
378
            (NoArg (\ opts -> Ok opts { optShowHelp = True}))
379
            "show help"
380

    
381
oShowVer :: OptType
382
oShowVer = Option "V" ["version"]
383
           (NoArg (\ opts -> Ok opts { optShowVer = True}))
384
           "show the version of the program"
385

    
386
oStdSpec :: OptType
387
oStdSpec = Option "" ["standard-alloc"]
388
             (ReqArg (\ inp opts -> do
389
                        tspec <- parseISpecString "standard" inp
390
                        return $ opts { optStdSpec = Just tspec } )
391
              "STDSPEC")
392
             "enable standard specs allocation, given as 'disk,ram,cpu'"
393

    
394
oTieredSpec :: OptType
395
oTieredSpec = Option "" ["tiered-alloc"]
396
             (ReqArg (\ inp opts -> do
397
                        tspec <- parseISpecString "tiered" inp
398
                        return $ opts { optTieredSpec = Just tspec } )
399
              "TSPEC")
400
             "enable tiered specs allocation, given as 'disk,ram,cpu'"
401

    
402
oReplay :: OptType
403
oReplay = Option "" ["replay"]
404
          (ReqArg (\ stat opts -> Ok opts { optReplay = Just stat } ) "STATE")
405
          "Pre-seed the random number generator with STATE"
406

    
407
oVerbose :: OptType
408
oVerbose = Option "v" ["verbose"]
409
           (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
410
           "increase the verbosity level"
411

    
412
-- * Functions
413

    
414
-- | Helper for parsing a yes\/no command line flag.
415
parseYesNo :: Bool         -- ^ Default value (when we get a @Nothing@)
416
           -> Maybe String -- ^ Parameter value
417
           -> Result Bool  -- ^ Resulting boolean value
418
parseYesNo v Nothing      = return v
419
parseYesNo _ (Just "yes") = return True
420
parseYesNo _ (Just "no")  = return False
421
parseYesNo _ (Just s)     = fail ("Invalid choice '" ++ s ++
422
                                  "', pass one of 'yes' or 'no'")
423

    
424
-- | Usage info.
425
usageHelp :: String -> [OptType] -> String
426
usageHelp progname =
427
  usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
428
             progname Version.version progname)
429

    
430
-- | Command line parser, using the 'Options' structure.
431
parseOpts :: [String]               -- ^ The command line arguments
432
          -> String                 -- ^ The program name
433
          -> [OptType]              -- ^ The supported command line options
434
          -> IO (Options, [String]) -- ^ The resulting options and leftover
435
                                    -- arguments
436
parseOpts argv progname options =
437
  case getOpt Permute options argv of
438
    (o, n, []) ->
439
      do
440
        let (pr, args) = (foldM (flip id) defaultOptions o, n)
441
        po <- case pr of
442
                Bad msg -> do
443
                  hPutStrLn stderr "Error while parsing command\
444
                                   \line arguments:"
445
                  hPutStrLn stderr msg
446
                  exitWith $ ExitFailure 1
447
                Ok val -> return val
448
        when (optShowHelp po) $ do
449
          putStr $ usageHelp progname options
450
          exitWith ExitSuccess
451
        when (optShowVer po) $ do
452
          printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
453
                 progname Version.version
454
                 compilerName (Data.Version.showVersion compilerVersion)
455
                 os arch :: IO ()
456
          exitWith ExitSuccess
457
        return (po, args)
458
    (_, _, errs) -> do
459
      hPutStrLn stderr $ "Command line error: "  ++ concat errs
460
      hPutStrLn stderr $ usageHelp progname options
461
      exitWith $ ExitFailure 2
462

    
463
-- | A shell script template for autogenerated scripts.
464
shTemplate :: String
465
shTemplate =
466
  printf "#!/bin/sh\n\n\
467
         \# Auto-generated script for executing cluster rebalancing\n\n\
468
         \# To stop, touch the file /tmp/stop-htools\n\n\
469
         \set -e\n\n\
470
         \check() {\n\
471
         \  if [ -f /tmp/stop-htools ]; then\n\
472
         \    echo 'Stop requested, exiting'\n\
473
         \    exit 0\n\
474
         \  fi\n\
475
         \}\n\n"
476

    
477
-- | Optionally print the node list.
478
maybePrintNodes :: Maybe [String]       -- ^ The field list
479
                -> String               -- ^ Informational message
480
                -> ([String] -> String) -- ^ Function to generate the listing
481
                -> IO ()
482
maybePrintNodes Nothing _ _ = return ()
483
maybePrintNodes (Just fields) msg fn = do
484
  hPutStrLn stderr ""
485
  hPutStrLn stderr (msg ++ " status:")
486
  hPutStrLn stderr $ fn fields
487

    
488

    
489
-- | Optionally print the instance list.
490
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
491
                -> String -- ^ Type of the instance map (e.g. initial)
492
                -> String -- ^ The instance data
493
                -> IO ()
494
maybePrintInsts do_print msg instdata =
495
  when do_print $ do
496
    hPutStrLn stderr ""
497
    hPutStrLn stderr $ msg ++ " instance map:"
498
    hPutStr stderr instdata
499

    
500
-- | Function to display warning messages from parsing the cluster
501
-- state.
502
maybeShowWarnings :: [String] -- ^ The warning messages
503
                  -> IO ()
504
maybeShowWarnings fix_msgs =
505
  unless (null fix_msgs) $ do
506
    hPutStrLn stderr "Warning: cluster has inconsistent data:"
507
    hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
508

    
509
-- | Set node properties based on command line options.
510
setNodeStatus :: Options -> Node.List -> IO Node.List
511
setNodeStatus opts fixed_nl = do
512
  let offline_passed = optOffline opts
513
      all_nodes = Container.elems fixed_nl
514
      offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
515
      offline_wrong = filter (not . goodLookupResult) offline_lkp
516
      offline_names = map lrContent offline_lkp
517
      offline_indices = map Node.idx $
518
                        filter (\n -> Node.name n `elem` offline_names)
519
                               all_nodes
520
      m_cpu = optMcpu opts
521
      m_dsk = optMdsk opts
522

    
523
  unless (null offline_wrong) $ do
524
         hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
525
                     (commaJoin (map lrContent offline_wrong)) :: IO ()
526
         exitWith $ ExitFailure 1
527

    
528
  let nm = Container.map (\n -> if Node.idx n `elem` offline_indices
529
                                then Node.setOffline n True
530
                                else n) fixed_nl
531
      nlf = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
532
            nm
533
  return nlf