Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ 9eeb0aa5

History | View | Annotate | Download (19.9 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
  , defaultOptions
34
  , Ganeti.HTools.CLI.parseOpts
35
  , parseOptsInner
36
  , parseYesNo
37
  , parseISpecString
38
  , shTemplate
39
  , maybePrintNodes
40
  , maybePrintInsts
41
  , maybeShowWarnings
42
  , printKeys
43
  , printFinal
44
  , setNodeStatus
45
  -- * The options
46
  , oDataFile
47
  , oDiskMoves
48
  , oDiskTemplate
49
  , oSpindleUse
50
  , oDynuFile
51
  , oEvacMode
52
  , oExInst
53
  , oExTags
54
  , oExecJobs
55
  , oGroup
56
  , oIAllocSrc
57
  , oInstMoves
58
  , oLuxiSocket
59
  , oMachineReadable
60
  , oMaxCpu
61
  , oMaxSolLength
62
  , oMinDisk
63
  , oMinGain
64
  , oMinGainLim
65
  , oMinScore
66
  , oNoHeaders
67
  , oNoSimulation
68
  , oNodeSim
69
  , oOfflineNode
70
  , oOutputDir
71
  , oPrintCommands
72
  , oPrintInsts
73
  , oPrintNodes
74
  , oQuiet
75
  , oRapiMaster
76
  , oSaveCluster
77
  , oSelInst
78
  , oShowHelp
79
  , oShowVer
80
  , oStdSpec
81
  , oTieredSpec
82
  , oVerbose
83
  ) where
84

    
85
import Control.Monad
86
import Data.Char (toUpper)
87
import Data.Maybe (fromMaybe)
88
import System.Console.GetOpt
89
import System.IO
90
import Text.Printf (printf)
91

    
92
import qualified Ganeti.HTools.Container as Container
93
import qualified Ganeti.HTools.Node as Node
94
import qualified Ganeti.Path as Path
95
import Ganeti.HTools.Types
96
import Ganeti.HTools.Utils
97
import Ganeti.BasicTypes
98
import Ganeti.Common as Common
99

    
100
-- * Data types
101

    
102
-- | Command line options structure.
103
data Options = Options
104
  { optDataFile    :: Maybe FilePath -- ^ Path to the cluster data file
105
  , optDiskMoves   :: Bool           -- ^ Allow disk moves
106
  , optInstMoves   :: Bool           -- ^ Allow instance moves
107
  , optDiskTemplate :: Maybe DiskTemplate  -- ^ Override for the disk template
108
  , optSpindleUse  :: Maybe Int      -- ^ Override for the spindle usage
109
  , optDynuFile    :: Maybe FilePath -- ^ Optional file with dynamic use data
110
  , optEvacMode    :: Bool           -- ^ Enable evacuation mode
111
  , optExInst      :: [String]       -- ^ Instances to be excluded
112
  , optExTags      :: Maybe [String] -- ^ Tags to use for exclusion
113
  , optExecJobs    :: Bool           -- ^ Execute the commands via Luxi
114
  , optGroup       :: Maybe GroupID  -- ^ The UUID of the group to process
115
  , optIAllocSrc   :: Maybe FilePath -- ^ The iallocation spec
116
  , optSelInst     :: [String]       -- ^ Instances to be excluded
117
  , optLuxi        :: Maybe FilePath -- ^ Collect data from Luxi
118
  , optMachineReadable :: Bool       -- ^ Output machine-readable format
119
  , optMaster      :: String         -- ^ Collect data from RAPI
120
  , optMaxLength   :: Int            -- ^ Stop after this many steps
121
  , optMcpu        :: Maybe Double   -- ^ Override max cpu ratio for nodes
122
  , optMdsk        :: Double         -- ^ Max disk usage ratio for nodes
123
  , optMinGain     :: Score          -- ^ Min gain we aim for in a step
124
  , optMinGainLim  :: Score          -- ^ Limit below which we apply mingain
125
  , optMinScore    :: Score          -- ^ The minimum score we aim for
126
  , optNoHeaders   :: Bool           -- ^ Do not show a header line
127
  , optNoSimulation :: Bool          -- ^ Skip the rebalancing dry-run
128
  , optNodeSim     :: [String]       -- ^ Cluster simulation mode
129
  , optOffline     :: [String]       -- ^ Names of offline nodes
130
  , optOutPath     :: FilePath       -- ^ Path to the output directory
131
  , optSaveCluster :: Maybe FilePath -- ^ Save cluster state to this file
132
  , optShowCmds    :: Maybe FilePath -- ^ Whether to show the command list
133
  , optShowHelp    :: Bool           -- ^ Just show the help
134
  , optShowInsts   :: Bool           -- ^ Whether to show the instance map
135
  , optShowNodes   :: Maybe [String] -- ^ Whether to show node status
136
  , optShowVer     :: Bool           -- ^ Just show the program version
137
  , optStdSpec     :: Maybe RSpec    -- ^ Requested standard specs
138
  , optTestCount   :: Maybe Int      -- ^ Optional test count override
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
  , optSpindleUse  = Nothing
152
  , optDynuFile    = Nothing
153
  , optEvacMode    = False
154
  , optExInst      = []
155
  , optExTags      = Nothing
156
  , optExecJobs    = False
157
  , optGroup       = Nothing
158
  , optIAllocSrc   = Nothing
159
  , optSelInst     = []
160
  , optLuxi        = Nothing
161
  , optMachineReadable = False
162
  , optMaster      = ""
163
  , optMaxLength   = -1
164
  , optMcpu        = Nothing
165
  , optMdsk        = defReservedDiskRatio
166
  , optMinGain     = 1e-2
167
  , optMinGainLim  = 1e-1
168
  , optMinScore    = 1e-9
169
  , optNoHeaders   = False
170
  , optNoSimulation = False
171
  , optNodeSim     = []
172
  , optOffline     = []
173
  , optOutPath     = "."
174
  , optSaveCluster = Nothing
175
  , optShowCmds    = Nothing
176
  , optShowHelp    = False
177
  , optShowInsts   = False
178
  , optShowNodes   = Nothing
179
  , optShowVer     = False
180
  , optStdSpec     = Nothing
181
  , optTestCount   = Nothing
182
  , optTieredSpec  = Nothing
183
  , optReplay      = Nothing
184
  , optVerbose     = 1
185
  }
186

    
187
-- | Abrreviation for the option type.
188
type OptType = GenericOptType Options
189

    
190
instance StandardOptions Options where
191
  helpRequested = optShowHelp
192
  verRequested  = optShowVer
193
  requestHelp o = o { optShowHelp = True }
194
  requestVer  o = o { optShowVer  = True }
195

    
196
-- * Helper functions
197

    
198
parseISpecString :: String -> String -> Result RSpec
199
parseISpecString descr inp = do
200
  let sp = sepSplit ',' inp
201
      err = Bad ("Invalid " ++ descr ++ " specification: '" ++ inp ++
202
                 "', expected disk,ram,cpu")
203
  when (length sp /= 3) err
204
  prs <- mapM (\(fn, val) -> fn val) $
205
         zip [ annotateResult (descr ++ " specs disk") . parseUnit
206
             , annotateResult (descr ++ " specs memory") . parseUnit
207
             , tryRead (descr ++ " specs cpus")
208
             ] sp
209
  case prs of
210
    [dsk, ram, cpu] -> return $ RSpec cpu ram dsk
211
    _ -> err
212

    
213
-- * Command line options
214

    
215
oDataFile :: OptType
216
oDataFile = Option "t" ["text-data"]
217
            (ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
218
            "the cluster data FILE"
219

    
220
oDiskMoves :: OptType
221
oDiskMoves = Option "" ["no-disk-moves"]
222
             (NoArg (\ opts -> Ok opts { optDiskMoves = False}))
223
             "disallow disk moves from the list of allowed instance changes,\
224
             \ thus allowing only the 'cheap' failover/migrate operations"
225

    
226
oDiskTemplate :: OptType
227
oDiskTemplate = Option "" ["disk-template"]
228
                (reqWithConversion diskTemplateFromRaw
229
                 (\dt opts -> Ok opts { optDiskTemplate = Just dt })
230
                 "TEMPLATE") "select the desired disk template"
231

    
232
oSpindleUse :: OptType
233
oSpindleUse = Option "" ["spindle-use"]
234
              (reqWithConversion (tryRead "parsing spindle-use")
235
               (\su opts -> do
236
                  when (su < 0) $
237
                       fail "Invalid value of the spindle-use\
238
                            \ (expected >= 0)"
239
                  return $ opts { optSpindleUse = Just su })
240
               "SPINDLES") "select how many virtual spindle instances use\
241
                           \ [default read from cluster]"
242

    
243
oSelInst :: OptType
244
oSelInst = Option "" ["select-instances"]
245
          (ReqArg (\ f opts -> Ok opts { optSelInst = sepSplit ',' f }) "INSTS")
246
          "only select given instances for any moves"
247

    
248
oInstMoves :: OptType
249
oInstMoves = Option "" ["no-instance-moves"]
250
             (NoArg (\ opts -> Ok opts { optInstMoves = False}))
251
             "disallow instance (primary node) moves from the list of allowed,\
252
             \ instance changes, thus allowing only slower, but sometimes\
253
             \ safer, drbd secondary changes"
254

    
255
oDynuFile :: OptType
256
oDynuFile = Option "U" ["dynu-file"]
257
            (ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
258
            "Import dynamic utilisation data from the given FILE"
259

    
260
oEvacMode :: OptType
261
oEvacMode = Option "E" ["evac-mode"]
262
            (NoArg (\opts -> Ok opts { optEvacMode = True }))
263
            "enable evacuation mode, where the algorithm only moves \
264
            \ instances away from offline and drained nodes"
265

    
266
oExInst :: OptType
267
oExInst = Option "" ["exclude-instances"]
268
          (ReqArg (\ f opts -> Ok opts { optExInst = sepSplit ',' f }) "INSTS")
269
          "exclude given instances from any moves"
270

    
271
oExTags :: OptType
272
oExTags = Option "" ["exclusion-tags"]
273
            (ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
274
             "TAG,...") "Enable instance exclusion based on given tag prefix"
275

    
276
oExecJobs :: OptType
277
oExecJobs = Option "X" ["exec"]
278
             (NoArg (\ opts -> Ok opts { optExecJobs = True}))
279
             "execute the suggested moves via Luxi (only available when using\
280
             \ it for data gathering)"
281

    
282
oGroup :: OptType
283
oGroup = Option "G" ["group"]
284
            (ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
285
            "the ID of the group to balance"
286

    
287
oIAllocSrc :: OptType
288
oIAllocSrc = Option "I" ["ialloc-src"]
289
             (ReqArg (\ f opts -> Ok opts { optIAllocSrc = Just f }) "FILE")
290
             "Specify an iallocator spec as the cluster data source"
291

    
292
oLuxiSocket :: OptType
293
oLuxiSocket = Option "L" ["luxi"]
294
              (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
295
                       fromMaybe Path.defaultLuxiSocket) "SOCKET")
296
              "collect data via Luxi, optionally using the given SOCKET path"
297

    
298
oMachineReadable :: OptType
299
oMachineReadable = Option "" ["machine-readable"]
300
                   (OptArg (\ f opts -> do
301
                     flag <- parseYesNo True f
302
                     return $ opts { optMachineReadable = flag }) "CHOICE")
303
          "enable machine readable output (pass either 'yes' or 'no' to\
304
          \ explicitly control the flag, or without an argument defaults to\
305
          \ yes"
306

    
307
oMaxCpu :: OptType
308
oMaxCpu = Option "" ["max-cpu"]
309
          (reqWithConversion (tryRead "parsing max-cpu")
310
           (\mcpu opts -> do
311
              when (mcpu <= 0) $
312
                   fail "Invalid value of the max-cpu ratio,\
313
                        \ expected >0"
314
              return $ opts { optMcpu = Just mcpu }) "RATIO")
315
          "maximum virtual-to-physical cpu ratio for nodes (from 0\
316
          \ upwards) [default read from cluster]"
317

    
318
oMaxSolLength :: OptType
319
oMaxSolLength = Option "l" ["max-length"]
320
                (reqWithConversion (tryRead "max solution length")
321
                 (\i opts -> Ok opts { optMaxLength = i }) "N")
322
                "cap the solution at this many balancing or allocation \
323
                \ rounds (useful for very unbalanced clusters or empty \
324
                \ clusters)"
325

    
326
oMinDisk :: OptType
327
oMinDisk = Option "" ["min-disk"]
328
           (reqWithConversion (tryRead "min free disk space")
329
            (\n opts -> Ok opts { optMdsk = n }) "RATIO")
330
           "minimum free disk space for nodes (between 0 and 1) [0]"
331

    
332
oMinGain :: OptType
333
oMinGain = Option "g" ["min-gain"]
334
           (reqWithConversion (tryRead "min gain")
335
            (\g opts -> Ok opts { optMinGain = g }) "DELTA")
336
            "minimum gain to aim for in a balancing step before giving up"
337

    
338
oMinGainLim :: OptType
339
oMinGainLim = Option "" ["min-gain-limit"]
340
            (reqWithConversion (tryRead "min gain limit")
341
             (\g opts -> Ok opts { optMinGainLim = g }) "SCORE")
342
            "minimum cluster score for which we start checking the min-gain"
343

    
344
oMinScore :: OptType
345
oMinScore = Option "e" ["min-score"]
346
            (reqWithConversion (tryRead "min score")
347
             (\e opts -> Ok opts { optMinScore = e }) "EPSILON")
348
            "mininum score to aim for"
349

    
350
oNoHeaders :: OptType
351
oNoHeaders = Option "" ["no-headers"]
352
             (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
353
             "do not show a header line"
354

    
355
oNoSimulation :: OptType
356
oNoSimulation = Option "" ["no-simulation"]
357
                (NoArg (\opts -> Ok opts {optNoSimulation = True}))
358
                "do not perform rebalancing simulation"
359

    
360
oNodeSim :: OptType
361
oNodeSim = Option "" ["simulate"]
362
            (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
363
            "simulate an empty cluster, given as\
364
            \ 'alloc_policy,num_nodes,disk,ram,cpu'"
365

    
366
oOfflineNode :: OptType
367
oOfflineNode = Option "O" ["offline"]
368
               (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
369
               "set node as offline"
370

    
371
oOutputDir :: OptType
372
oOutputDir = Option "d" ["output-dir"]
373
             (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
374
             "directory in which to write output files"
375

    
376
oPrintCommands :: OptType
377
oPrintCommands = Option "C" ["print-commands"]
378
                 (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
379
                          fromMaybe "-")
380
                  "FILE")
381
                 "print the ganeti command list for reaching the solution,\
382
                 \ if an argument is passed then write the commands to a\
383
                 \ file named as such"
384

    
385
oPrintInsts :: OptType
386
oPrintInsts = Option "" ["print-instances"]
387
              (NoArg (\ opts -> Ok opts { optShowInsts = True }))
388
              "print the final instance map"
389

    
390
oPrintNodes :: OptType
391
oPrintNodes = Option "p" ["print-nodes"]
392
              (OptArg ((\ f opts ->
393
                          let (prefix, realf) = case f of
394
                                                  '+':rest -> (["+"], rest)
395
                                                  _ -> ([], f)
396
                              splitted = prefix ++ sepSplit ',' realf
397
                          in Ok opts { optShowNodes = Just splitted }) .
398
                       fromMaybe []) "FIELDS")
399
              "print the final node list"
400

    
401
oQuiet :: OptType
402
oQuiet = Option "q" ["quiet"]
403
         (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
404
         "decrease the verbosity level"
405

    
406
oRapiMaster :: OptType
407
oRapiMaster = Option "m" ["master"]
408
              (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
409
              "collect data via RAPI at the given ADDRESS"
410

    
411
oSaveCluster :: OptType
412
oSaveCluster = Option "S" ["save"]
413
            (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
414
            "Save cluster state at the end of the processing to FILE"
415

    
416
oStdSpec :: OptType
417
oStdSpec = Option "" ["standard-alloc"]
418
             (ReqArg (\ inp opts -> do
419
                        tspec <- parseISpecString "standard" inp
420
                        return $ opts { optStdSpec = Just tspec } )
421
              "STDSPEC")
422
             "enable standard specs allocation, given as 'disk,ram,cpu'"
423

    
424
oTieredSpec :: OptType
425
oTieredSpec = Option "" ["tiered-alloc"]
426
             (ReqArg (\ inp opts -> do
427
                        tspec <- parseISpecString "tiered" inp
428
                        return $ opts { optTieredSpec = Just tspec } )
429
              "TSPEC")
430
             "enable tiered specs allocation, given as 'disk,ram,cpu'"
431

    
432
oVerbose :: OptType
433
oVerbose = Option "v" ["verbose"]
434
           (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
435
           "increase the verbosity level"
436

    
437
-- * Functions
438

    
439
-- | Wrapper over 'Common.parseOpts' with our custom options.
440
parseOpts :: [String]               -- ^ The command line arguments
441
          -> String                 -- ^ The program name
442
          -> [OptType]              -- ^ The supported command line options
443
          -> IO (Options, [String]) -- ^ The resulting options and leftover
444
                                    -- arguments
445
parseOpts = Common.parseOpts defaultOptions
446

    
447

    
448
-- | A shell script template for autogenerated scripts.
449
shTemplate :: String
450
shTemplate =
451
  printf "#!/bin/sh\n\n\
452
         \# Auto-generated script for executing cluster rebalancing\n\n\
453
         \# To stop, touch the file /tmp/stop-htools\n\n\
454
         \set -e\n\n\
455
         \check() {\n\
456
         \  if [ -f /tmp/stop-htools ]; then\n\
457
         \    echo 'Stop requested, exiting'\n\
458
         \    exit 0\n\
459
         \  fi\n\
460
         \}\n\n"
461

    
462
-- | Optionally print the node list.
463
maybePrintNodes :: Maybe [String]       -- ^ The field list
464
                -> String               -- ^ Informational message
465
                -> ([String] -> String) -- ^ Function to generate the listing
466
                -> IO ()
467
maybePrintNodes Nothing _ _ = return ()
468
maybePrintNodes (Just fields) msg fn = do
469
  hPutStrLn stderr ""
470
  hPutStrLn stderr (msg ++ " status:")
471
  hPutStrLn stderr $ fn fields
472

    
473
-- | Optionally print the instance list.
474
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
475
                -> String -- ^ Type of the instance map (e.g. initial)
476
                -> String -- ^ The instance data
477
                -> IO ()
478
maybePrintInsts do_print msg instdata =
479
  when do_print $ do
480
    hPutStrLn stderr ""
481
    hPutStrLn stderr $ msg ++ " instance map:"
482
    hPutStr stderr instdata
483

    
484
-- | Function to display warning messages from parsing the cluster
485
-- state.
486
maybeShowWarnings :: [String] -- ^ The warning messages
487
                  -> IO ()
488
maybeShowWarnings fix_msgs =
489
  unless (null fix_msgs) $ do
490
    hPutStrLn stderr "Warning: cluster has inconsistent data:"
491
    hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
492

    
493
-- | Format a list of key, value as a shell fragment.
494
printKeys :: String              -- ^ Prefix to printed variables
495
          -> [(String, String)]  -- ^ List of (key, value) pairs to be printed
496
          -> IO ()
497
printKeys prefix =
498
  mapM_ (\(k, v) ->
499
           printf "%s_%s=%s\n" prefix (map toUpper k) (ensureQuoted v))
500

    
501
-- | Prints the final @OK@ marker in machine readable output.
502
printFinal :: String    -- ^ Prefix to printed variable
503
           -> Bool      -- ^ Whether output should be machine readable;
504
                        -- note: if not, there is nothing to print
505
           -> IO ()
506
printFinal prefix True =
507
  -- this should be the final entry
508
  printKeys prefix [("OK", "1")]
509

    
510
printFinal _ False = return ()
511

    
512
-- | Potentially set the node as offline based on passed offline list.
513
setNodeOffline :: [Ndx] -> Node.Node -> Node.Node
514
setNodeOffline offline_indices n =
515
  if Node.idx n `elem` offline_indices
516
    then Node.setOffline n True
517
    else n
518

    
519
-- | Set node properties based on command line options.
520
setNodeStatus :: Options -> Node.List -> IO Node.List
521
setNodeStatus opts fixed_nl = do
522
  let offline_passed = optOffline opts
523
      all_nodes = Container.elems fixed_nl
524
      offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
525
      offline_wrong = filter (not . goodLookupResult) offline_lkp
526
      offline_names = map lrContent offline_lkp
527
      offline_indices = map Node.idx $
528
                        filter (\n -> Node.name n `elem` offline_names)
529
                               all_nodes
530
      m_cpu = optMcpu opts
531
      m_dsk = optMdsk opts
532

    
533
  unless (null offline_wrong) .
534
         exitErr $ printf "wrong node name(s) set as offline: %s\n"
535
                   (commaJoin (map lrContent offline_wrong))
536
  let setMCpuFn = case m_cpu of
537
                    Nothing -> id
538
                    Just new_mcpu -> flip Node.setMcpu new_mcpu
539
  let nm = Container.map (setNodeOffline offline_indices .
540
                          flip Node.setMdsk m_dsk .
541
                          setMCpuFn) fixed_nl
542
  return nm