Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ 7345b69b

History | View | Annotate | Download (20.1 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
-- * Command line options
188

    
189
oDataFile :: OptType
190
oDataFile = Option "t" ["text-data"]
191
            (ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
192
            "the cluster data FILE"
193

    
194
oDiskMoves :: OptType
195
oDiskMoves = Option "" ["no-disk-moves"]
196
             (NoArg (\ opts -> Ok opts { optDiskMoves = False}))
197
             "disallow disk moves from the list of allowed instance changes,\
198
             \ thus allowing only the 'cheap' failover/migrate operations"
199

    
200
oDiskTemplate :: OptType
201
oDiskTemplate = Option "" ["disk-template"]
202
                (ReqArg (\ t opts -> do
203
                           dt <- diskTemplateFromRaw t
204
                           return $ opts { optDiskTemplate = dt }) "TEMPLATE")
205
                "select the desired disk template"
206

    
207
oSelInst :: OptType
208
oSelInst = Option "" ["select-instances"]
209
          (ReqArg (\ f opts -> Ok opts { optSelInst = sepSplit ',' f }) "INSTS")
210
          "only select given instances for any moves"
211

    
212
oInstMoves :: OptType
213
oInstMoves = Option "" ["no-instance-moves"]
214
             (NoArg (\ opts -> Ok opts { optInstMoves = False}))
215
             "disallow instance (primary node) moves from the list of allowed,\
216
             \ instance changes, thus allowing only slower, but sometimes\
217
             \ safer, drbd secondary changes"
218

    
219
oDynuFile :: OptType
220
oDynuFile = Option "U" ["dynu-file"]
221
            (ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
222
            "Import dynamic utilisation data from the given FILE"
223

    
224
oEvacMode :: OptType
225
oEvacMode = Option "E" ["evac-mode"]
226
            (NoArg (\opts -> Ok opts { optEvacMode = True }))
227
            "enable evacuation mode, where the algorithm only moves \
228
            \ instances away from offline and drained nodes"
229

    
230
oExInst :: OptType
231
oExInst = Option "" ["exclude-instances"]
232
          (ReqArg (\ f opts -> Ok opts { optExInst = sepSplit ',' f }) "INSTS")
233
          "exclude given instances from any moves"
234

    
235
oExTags :: OptType
236
oExTags = Option "" ["exclusion-tags"]
237
            (ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
238
             "TAG,...") "Enable instance exclusion based on given tag prefix"
239

    
240
oExecJobs :: OptType
241
oExecJobs = Option "X" ["exec"]
242
             (NoArg (\ opts -> Ok opts { optExecJobs = True}))
243
             "execute the suggested moves via Luxi (only available when using\
244
             \ it for data gathering)"
245

    
246
oGroup :: OptType
247
oGroup = Option "G" ["group"]
248
            (ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
249
            "the ID of the group to balance"
250

    
251
oIDisk :: OptType
252
oIDisk = Option "" ["disk"]
253
         (ReqArg (\ d opts -> do
254
                    dsk <- annotateResult "--disk option" (parseUnit d)
255
                    let ospec = optISpec opts
256
                        nspec = ospec { rspecDsk = dsk }
257
                    return $ opts { optISpec = nspec }) "DISK")
258
         "disk size for instances"
259

    
260
oIMem :: OptType
261
oIMem = Option "" ["memory"]
262
        (ReqArg (\ m opts -> do
263
                   mem <- annotateResult "--memory option" (parseUnit m)
264
                   let ospec = optISpec opts
265
                       nspec = ospec { rspecMem = mem }
266
                   return $ opts { optISpec = nspec }) "MEMORY")
267
        "memory size for instances"
268

    
269
oIVcpus :: OptType
270
oIVcpus = Option "" ["vcpus"]
271
          (ReqArg (\ p opts -> do
272
                     vcpus <- tryRead "--vcpus option" p
273
                     let ospec = optISpec opts
274
                         nspec = ospec { rspecCpu = vcpus }
275
                     return $ opts { optISpec = nspec }) "NUM")
276
          "number of virtual cpus for instances"
277

    
278
oLuxiSocket :: OptType
279
oLuxiSocket = Option "L" ["luxi"]
280
              (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
281
                       fromMaybe defaultLuxiSocket) "SOCKET")
282
              "collect data via Luxi, optionally using the given SOCKET path"
283

    
284
oMachineReadable :: OptType
285
oMachineReadable = Option "" ["machine-readable"]
286
                   (OptArg (\ f opts -> do
287
                     flag <- parseYesNo True f
288
                     return $ opts { optMachineReadable = flag }) "CHOICE")
289
          "enable machine readable output (pass either 'yes' or 'no' to\
290
          \ explicitely control the flag, or without an argument defaults to\
291
          \ yes"
292

    
293
oMaxCpu :: OptType
294
oMaxCpu = Option "" ["max-cpu"]
295
          (ReqArg (\ n opts -> Ok opts { optMcpu = read n }) "RATIO")
296
          "maximum virtual-to-physical cpu ratio for nodes (from 1\
297
          \ upwards) [64]"
298

    
299
oMaxSolLength :: OptType
300
oMaxSolLength = Option "l" ["max-length"]
301
                (ReqArg (\ i opts -> Ok opts { optMaxLength = read i }) "N")
302
                "cap the solution at this many balancing or allocation \
303
                \ rounds (useful for very unbalanced clusters or empty \
304
                \ clusters)"
305

    
306
oMinDisk :: OptType
307
oMinDisk = Option "" ["min-disk"]
308
           (ReqArg (\ n opts -> Ok opts { optMdsk = read n }) "RATIO")
309
           "minimum free disk space for nodes (between 0 and 1) [0]"
310

    
311
oMinGain :: OptType
312
oMinGain = Option "g" ["min-gain"]
313
            (ReqArg (\ g opts -> Ok opts { optMinGain = read g }) "DELTA")
314
            "minimum gain to aim for in a balancing step before giving up"
315

    
316
oMinGainLim :: OptType
317
oMinGainLim = Option "" ["min-gain-limit"]
318
            (ReqArg (\ g opts -> Ok opts { optMinGainLim = read g }) "SCORE")
319
            "minimum cluster score for which we start checking the min-gain"
320

    
321
oMinScore :: OptType
322
oMinScore = Option "e" ["min-score"]
323
            (ReqArg (\ e opts -> Ok opts { optMinScore = read e }) "EPSILON")
324
            "mininum score to aim for"
325

    
326
oNoHeaders :: OptType
327
oNoHeaders = Option "" ["no-headers"]
328
             (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
329
             "do not show a header line"
330

    
331
oNodeSim :: OptType
332
oNodeSim = Option "" ["simulate"]
333
            (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
334
            "simulate an empty cluster, given as 'num_nodes,disk,ram,cpu'"
335

    
336
oOfflineNode :: OptType
337
oOfflineNode = Option "O" ["offline"]
338
               (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
339
               "set node as offline"
340

    
341
oOutputDir :: OptType
342
oOutputDir = Option "d" ["output-dir"]
343
             (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
344
             "directory in which to write output files"
345

    
346
oPrintCommands :: OptType
347
oPrintCommands = Option "C" ["print-commands"]
348
                 (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
349
                          fromMaybe "-")
350
                  "FILE")
351
                 "print the ganeti command list for reaching the solution,\
352
                 \ if an argument is passed then write the commands to a\
353
                 \ file named as such"
354

    
355
oPrintInsts :: OptType
356
oPrintInsts = Option "" ["print-instances"]
357
              (NoArg (\ opts -> Ok opts { optShowInsts = True }))
358
              "print the final instance map"
359

    
360
oPrintNodes :: OptType
361
oPrintNodes = Option "p" ["print-nodes"]
362
              (OptArg ((\ f opts ->
363
                          let (prefix, realf) = case f of
364
                                                  '+':rest -> (["+"], rest)
365
                                                  _ -> ([], f)
366
                              splitted = prefix ++ sepSplit ',' realf
367
                          in Ok opts { optShowNodes = Just splitted }) .
368
                       fromMaybe []) "FIELDS")
369
              "print the final node list"
370

    
371
oQuiet :: OptType
372
oQuiet = Option "q" ["quiet"]
373
         (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
374
         "decrease the verbosity level"
375

    
376
oRapiMaster :: OptType
377
oRapiMaster = Option "m" ["master"]
378
              (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
379
              "collect data via RAPI at the given ADDRESS"
380

    
381
oSaveCluster :: OptType
382
oSaveCluster = Option "S" ["save"]
383
            (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
384
            "Save cluster state at the end of the processing to FILE"
385

    
386
oShowHelp :: OptType
387
oShowHelp = Option "h" ["help"]
388
            (NoArg (\ opts -> Ok opts { optShowHelp = True}))
389
            "show help"
390

    
391
oShowVer :: OptType
392
oShowVer = Option "V" ["version"]
393
           (NoArg (\ opts -> Ok opts { optShowVer = True}))
394
           "show the version of the program"
395

    
396
oTieredSpec :: OptType
397
oTieredSpec = Option "" ["tiered-alloc"]
398
             (ReqArg (\ inp opts -> do
399
                        let sp = sepSplit ',' inp
400
                        prs <- mapM (\(fn, val) -> fn val) $
401
                               zip [ annotateResult "tiered specs memory" .
402
                                     parseUnit
403
                                   , annotateResult "tiered specs disk" .
404
                                     parseUnit
405
                                   , tryRead "tiered specs cpus"
406
                                   ] sp
407
                        tspec <-
408
                          case prs of
409
                            [dsk, ram, cpu] -> return $ RSpec cpu ram dsk
410
                            _ -> Bad $ "Invalid specification: " ++ inp ++
411
                                 ", expected disk,ram,cpu"
412
                        return $ opts { optTieredSpec = Just tspec } )
413
              "TSPEC")
414
             "enable tiered specs allocation, given as 'disk,ram,cpu'"
415

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

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

    
426
-- * Functions
427

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

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

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

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

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

    
502

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

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

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

    
537
  when (not (null offline_wrong)) $ do
538
         hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
539
                     (commaJoin (map lrContent offline_wrong)) :: IO ()
540
         exitWith $ ExitFailure 1
541

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