Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ 7da760ca

History | View | Annotate | Download (20 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 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
  , shTemplate
35
  , defaultLuxiSocket
36
  , maybePrintNodes
37
  , maybePrintInsts
38
  , maybeShowWarnings
39
  , setNodeStatus
40
  -- * The options
41
  , oDataFile
42
  , oDiskMoves
43
  , oDiskTemplate
44
  , oDynuFile
45
  , oEvacMode
46
  , oExInst
47
  , oExTags
48
  , oExecJobs
49
  , oGroup
50
  , oIDisk
51
  , oIMem
52
  , oIVcpus
53
  , oInstMoves
54
  , oLuxiSocket
55
  , oMachineReadable
56
  , oMaxCpu
57
  , oMaxSolLength
58
  , oMinDisk
59
  , oMinGain
60
  , oMinGainLim
61
  , oMinScore
62
  , oNoHeaders
63
  , oNodeSim
64
  , oOfflineNode
65
  , oOutputDir
66
  , oPrintCommands
67
  , oPrintInsts
68
  , oPrintNodes
69
  , oQuiet
70
  , oRapiMaster
71
  , oReplay
72
  , oSaveCluster
73
  , oSelInst
74
  , oShowHelp
75
  , oShowVer
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 :: DiskTemplate  -- ^ The requested 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
  , optISpec       :: RSpec          -- ^ Requested instance specs
121
  , optLuxi        :: Maybe FilePath -- ^ Collect data from Luxi
122
  , optMachineReadable :: Bool       -- ^ Output machine-readable format
123
  , optMaster      :: String         -- ^ Collect data from RAPI
124
  , optMaxLength   :: Int            -- ^ Stop after this many steps
125
  , optMcpu        :: Double         -- ^ Max cpu ratio for nodes
126
  , optMdsk        :: Double         -- ^ Max disk usage ratio for nodes
127
  , optMinGain     :: Score          -- ^ Min gain we aim for in a step
128
  , optMinGainLim  :: Score          -- ^ Limit below which we apply mingain
129
  , optMinScore    :: Score          -- ^ The minimum score we aim for
130
  , optNoHeaders   :: Bool           -- ^ Do not show a header line
131
  , optNodeSim     :: [String]       -- ^ Cluster simulation mode
132
  , optOffline     :: [String]       -- ^ Names of offline nodes
133
  , optOutPath     :: FilePath       -- ^ Path to the output directory
134
  , optSaveCluster :: Maybe FilePath -- ^ Save cluster state to this file
135
  , optShowCmds    :: Maybe FilePath -- ^ Whether to show the command list
136
  , optShowHelp    :: Bool           -- ^ Just show the help
137
  , optShowInsts   :: Bool           -- ^ Whether to show the instance map
138
  , optShowNodes   :: Maybe [String] -- ^ Whether to show node status
139
  , optShowVer     :: Bool           -- ^ Just show the program version
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 = DTDrbd8
152
  , optDynuFile    = Nothing
153
  , optEvacMode    = False
154
  , optExInst      = []
155
  , optExTags      = Nothing
156
  , optExecJobs    = False
157
  , optGroup       = Nothing
158
  , optSelInst     = []
159
  , optISpec       = RSpec 1 4096 102400
160
  , optLuxi        = Nothing
161
  , optMachineReadable = False
162
  , optMaster      = ""
163
  , optMaxLength   = -1
164
  , optMcpu        = defVcpuRatio
165
  , optMdsk        = defReservedDiskRatio
166
  , optMinGain     = 1e-2
167
  , optMinGainLim  = 1e-1
168
  , optMinScore    = 1e-9
169
  , optNoHeaders   = False
170
  , optNodeSim     = []
171
  , optOffline     = []
172
  , optOutPath     = "."
173
  , optSaveCluster = Nothing
174
  , optShowCmds    = Nothing
175
  , optShowHelp    = False
176
  , optShowInsts   = False
177
  , optShowNodes   = Nothing
178
  , optShowVer     = False
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
  prs <- mapM (\(fn, val) -> fn val) $
193
         zip [ annotateResult (descr ++ " specs memory") . parseUnit
194
             , annotateResult (descr ++ " specs disk") . parseUnit
195
             , tryRead (descr ++ " specs cpus")
196
             ] sp
197
  case prs of
198
    [dsk, ram, cpu] -> return $ RSpec cpu ram dsk
199
    _ -> Bad $ "Invalid " ++ descr ++ " specification: '" ++ inp ++
200
         "', expected disk,ram,cpu"
201

    
202
-- * Command line options
203

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

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

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

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

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

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

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

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

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

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

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

    
266
oIDisk :: OptType
267
oIDisk = Option "" ["disk"]
268
         (ReqArg (\ d opts -> do
269
                    dsk <- annotateResult "--disk option" (parseUnit d)
270
                    let ospec = optISpec opts
271
                        nspec = ospec { rspecDsk = dsk }
272
                    return $ opts { optISpec = nspec }) "DISK")
273
         "disk size for instances"
274

    
275
oIMem :: OptType
276
oIMem = Option "" ["memory"]
277
        (ReqArg (\ m opts -> do
278
                   mem <- annotateResult "--memory option" (parseUnit m)
279
                   let ospec = optISpec opts
280
                       nspec = ospec { rspecMem = mem }
281
                   return $ opts { optISpec = nspec }) "MEMORY")
282
        "memory size for instances"
283

    
284
oIVcpus :: OptType
285
oIVcpus = Option "" ["vcpus"]
286
          (ReqArg (\ p opts -> do
287
                     vcpus <- tryRead "--vcpus option" p
288
                     let ospec = optISpec opts
289
                         nspec = ospec { rspecCpu = vcpus }
290
                     return $ opts { optISpec = nspec }) "NUM")
291
          "number of virtual cpus for instances"
292

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

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

    
308
oMaxCpu :: OptType
309
oMaxCpu = Option "" ["max-cpu"]
310
          (ReqArg (\ n opts -> Ok opts { optMcpu = read n }) "RATIO")
311
          "maximum virtual-to-physical cpu ratio for nodes (from 1\
312
          \ upwards) [64]"
313

    
314
oMaxSolLength :: OptType
315
oMaxSolLength = Option "l" ["max-length"]
316
                (ReqArg (\ i opts -> Ok opts { optMaxLength = read i }) "N")
317
                "cap the solution at this many balancing or allocation \
318
                \ rounds (useful for very unbalanced clusters or empty \
319
                \ clusters)"
320

    
321
oMinDisk :: OptType
322
oMinDisk = Option "" ["min-disk"]
323
           (ReqArg (\ n opts -> Ok opts { optMdsk = read n }) "RATIO")
324
           "minimum free disk space for nodes (between 0 and 1) [0]"
325

    
326
oMinGain :: OptType
327
oMinGain = Option "g" ["min-gain"]
328
            (ReqArg (\ g opts -> Ok opts { optMinGain = read g }) "DELTA")
329
            "minimum gain to aim for in a balancing step before giving up"
330

    
331
oMinGainLim :: OptType
332
oMinGainLim = Option "" ["min-gain-limit"]
333
            (ReqArg (\ g opts -> Ok opts { optMinGainLim = read g }) "SCORE")
334
            "minimum cluster score for which we start checking the min-gain"
335

    
336
oMinScore :: OptType
337
oMinScore = Option "e" ["min-score"]
338
            (ReqArg (\ e opts -> Ok opts { optMinScore = read e }) "EPSILON")
339
            "mininum score to aim for"
340

    
341
oNoHeaders :: OptType
342
oNoHeaders = Option "" ["no-headers"]
343
             (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
344
             "do not show a header line"
345

    
346
oNodeSim :: OptType
347
oNodeSim = Option "" ["simulate"]
348
            (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
349
            "simulate an empty cluster, given as 'num_nodes,disk,ram,cpu'"
350

    
351
oOfflineNode :: OptType
352
oOfflineNode = Option "O" ["offline"]
353
               (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
354
               "set node as offline"
355

    
356
oOutputDir :: OptType
357
oOutputDir = Option "d" ["output-dir"]
358
             (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
359
             "directory in which to write output files"
360

    
361
oPrintCommands :: OptType
362
oPrintCommands = Option "C" ["print-commands"]
363
                 (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
364
                          fromMaybe "-")
365
                  "FILE")
366
                 "print the ganeti command list for reaching the solution,\
367
                 \ if an argument is passed then write the commands to a\
368
                 \ file named as such"
369

    
370
oPrintInsts :: OptType
371
oPrintInsts = Option "" ["print-instances"]
372
              (NoArg (\ opts -> Ok opts { optShowInsts = True }))
373
              "print the final instance map"
374

    
375
oPrintNodes :: OptType
376
oPrintNodes = Option "p" ["print-nodes"]
377
              (OptArg ((\ f opts ->
378
                          let (prefix, realf) = case f of
379
                                                  '+':rest -> (["+"], rest)
380
                                                  _ -> ([], f)
381
                              splitted = prefix ++ sepSplit ',' realf
382
                          in Ok opts { optShowNodes = Just splitted }) .
383
                       fromMaybe []) "FIELDS")
384
              "print the final node list"
385

    
386
oQuiet :: OptType
387
oQuiet = Option "q" ["quiet"]
388
         (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
389
         "decrease the verbosity level"
390

    
391
oRapiMaster :: OptType
392
oRapiMaster = Option "m" ["master"]
393
              (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
394
              "collect data via RAPI at the given ADDRESS"
395

    
396
oSaveCluster :: OptType
397
oSaveCluster = Option "S" ["save"]
398
            (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
399
            "Save cluster state at the end of the processing to FILE"
400

    
401
oShowHelp :: OptType
402
oShowHelp = Option "h" ["help"]
403
            (NoArg (\ opts -> Ok opts { optShowHelp = True}))
404
            "show help"
405

    
406
oShowVer :: OptType
407
oShowVer = Option "V" ["version"]
408
           (NoArg (\ opts -> Ok opts { optShowVer = True}))
409
           "show the version of the program"
410

    
411
oTieredSpec :: OptType
412
oTieredSpec = Option "" ["tiered-alloc"]
413
             (ReqArg (\ inp opts -> do
414
                        tspec <- parseISpecString "tiered" inp
415
                        return $ opts { optTieredSpec = Just tspec } )
416
              "TSPEC")
417
             "enable tiered specs allocation, given as 'disk,ram,cpu'"
418

    
419
oReplay :: OptType
420
oReplay = Option "" ["replay"]
421
          (ReqArg (\ stat opts -> Ok opts { optReplay = Just stat } ) "STATE")
422
          "Pre-seed the random number generator with STATE"
423

    
424
oVerbose :: OptType
425
oVerbose = Option "v" ["verbose"]
426
           (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
427
           "increase the verbosity level"
428

    
429
-- * Functions
430

    
431
-- | Helper for parsing a yes\/no command line flag.
432
parseYesNo :: Bool         -- ^ Default whalue (when we get a @Nothing@)
433
           -> Maybe String -- ^ Parameter value
434
           -> Result Bool  -- ^ Resulting boolean value
435
parseYesNo v Nothing      = return v
436
parseYesNo _ (Just "yes") = return True
437
parseYesNo _ (Just "no")  = return False
438
parseYesNo _ (Just s)     = fail $ "Invalid choice '" ++ s ++
439
                            "', pass one of 'yes' or 'no'"
440

    
441
-- | Usage info.
442
usageHelp :: String -> [OptType] -> String
443
usageHelp progname =
444
  usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
445
             progname Version.version progname)
446

    
447
-- | Command line parser, using the 'Options' structure.
448
parseOpts :: [String]               -- ^ The command line arguments
449
          -> String                 -- ^ The program name
450
          -> [OptType]              -- ^ The supported command line options
451
          -> IO (Options, [String]) -- ^ The resulting options and leftover
452
                                    -- arguments
453
parseOpts argv progname options =
454
  case getOpt Permute options argv of
455
    (o, n, []) ->
456
      do
457
        let (pr, args) = (foldM (flip id) defaultOptions o, n)
458
        po <- case pr of
459
                Bad msg -> do
460
                  hPutStrLn stderr "Error while parsing command\
461
                                   \line arguments:"
462
                  hPutStrLn stderr msg
463
                  exitWith $ ExitFailure 1
464
                Ok val -> return val
465
        when (optShowHelp po) $ do
466
          putStr $ usageHelp progname options
467
          exitWith ExitSuccess
468
        when (optShowVer po) $ do
469
          printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
470
                 progname Version.version
471
                 compilerName (Data.Version.showVersion compilerVersion)
472
                 os arch :: IO ()
473
          exitWith ExitSuccess
474
        return (po, args)
475
    (_, _, errs) -> do
476
      hPutStrLn stderr $ "Command line error: "  ++ concat errs
477
      hPutStrLn stderr $ usageHelp progname options
478
      exitWith $ ExitFailure 2
479

    
480
-- | A shell script template for autogenerated scripts.
481
shTemplate :: String
482
shTemplate =
483
  printf "#!/bin/sh\n\n\
484
         \# Auto-generated script for executing cluster rebalancing\n\n\
485
         \# To stop, touch the file /tmp/stop-htools\n\n\
486
         \set -e\n\n\
487
         \check() {\n\
488
         \  if [ -f /tmp/stop-htools ]; then\n\
489
         \    echo 'Stop requested, exiting'\n\
490
         \    exit 0\n\
491
         \  fi\n\
492
         \}\n\n"
493

    
494
-- | Optionally print the node list.
495
maybePrintNodes :: Maybe [String]       -- ^ The field list
496
                -> String               -- ^ Informational message
497
                -> ([String] -> String) -- ^ Function to generate the listing
498
                -> IO ()
499
maybePrintNodes Nothing _ _ = return ()
500
maybePrintNodes (Just fields) msg fn = do
501
  hPutStrLn stderr ""
502
  hPutStrLn stderr (msg ++ " status:")
503
  hPutStrLn stderr $ fn fields
504

    
505

    
506
-- | Optionally print the instance list.
507
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
508
                -> String -- ^ Type of the instance map (e.g. initial)
509
                -> String -- ^ The instance data
510
                -> IO ()
511
maybePrintInsts do_print msg instdata =
512
  when do_print $ do
513
    hPutStrLn stderr ""
514
    hPutStrLn stderr $ msg ++ " instance map:"
515
    hPutStr stderr instdata
516

    
517
-- | Function to display warning messages from parsing the cluster
518
-- state.
519
maybeShowWarnings :: [String] -- ^ The warning messages
520
                  -> IO ()
521
maybeShowWarnings fix_msgs =
522
  unless (null fix_msgs) $ do
523
    hPutStrLn stderr "Warning: cluster has inconsistent data:"
524
    hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
525

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

    
540
  unless (null offline_wrong) $ do
541
         hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
542
                     (commaJoin (map lrContent offline_wrong)) :: IO ()
543
         exitWith $ ExitFailure 1
544

    
545
  let nm = Container.map (\n -> if Node.idx n `elem` offline_indices
546
                                then Node.setOffline n True
547
                                else n) fixed_nl
548
      nlf = Container.map (flip Node.setMdsk m_dsk . flip Node.setMcpu m_cpu)
549
            nm
550
  return nlf