Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ 8b5a517a

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

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

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

    
96
-- * Constants
97

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

    
104
-- * Data types
105

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

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

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

    
186
-- * Helper functions
187

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

    
203
-- * Command line options
204

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
411
-- * Functions
412

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

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

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

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

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

    
487

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

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

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

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

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