Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / CLI.hs @ 30ce253e

History | View | Annotate | Download (23.8 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.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, 2013 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
  , oForce
56
  , oGroup
57
  , oIAllocSrc
58
  , oIgnoreNonRedundant
59
  , oInstMoves
60
  , oJobDelay
61
  , genOLuxiSocket
62
  , oLuxiSocket
63
  , oMachineReadable
64
  , oMaxCpu
65
  , oMaxSolLength
66
  , oMinDisk
67
  , oMinGain
68
  , oMinGainLim
69
  , oMinScore
70
  , oNoHeaders
71
  , oNoSimulation
72
  , oNodeSim
73
  , oNodeTags
74
  , oOfflineMaintenance
75
  , oOfflineNode
76
  , oOneStepOnly
77
  , oOutputDir
78
  , oPrintCommands
79
  , oPrintInsts
80
  , oPrintMoves
81
  , oPrintNodes
82
  , oQuiet
83
  , oRapiMaster
84
  , oSaveCluster
85
  , oSelInst
86
  , oShowHelp
87
  , oShowVer
88
  , oShowComp
89
  , oSkipNonRedundant
90
  , oStdSpec
91
  , oTieredSpec
92
  , oVerbose
93
  , oPriority
94
  , genericOpts
95
  ) where
96

    
97
import Control.Monad
98
import Data.Char (toUpper)
99
import Data.Maybe (fromMaybe)
100
import System.Console.GetOpt
101
import System.IO
102
import Text.Printf (printf)
103

    
104
import qualified Ganeti.HTools.Container as Container
105
import qualified Ganeti.HTools.Node as Node
106
import qualified Ganeti.Path as Path
107
import Ganeti.HTools.Types
108
import Ganeti.BasicTypes
109
import Ganeti.Common as Common
110
import Ganeti.Types
111
import Ganeti.Utils
112

    
113
-- * Data types
114

    
115
-- | Command line options structure.
116
data Options = Options
117
  { optDataFile    :: Maybe FilePath -- ^ Path to the cluster data file
118
  , optDiskMoves   :: Bool           -- ^ Allow disk moves
119
  , optInstMoves   :: Bool           -- ^ Allow instance moves
120
  , optDiskTemplate :: Maybe DiskTemplate  -- ^ Override for the disk template
121
  , optSpindleUse  :: Maybe Int      -- ^ Override for the spindle usage
122
  , optDynuFile    :: Maybe FilePath -- ^ Optional file with dynamic use data
123
  , optEvacMode    :: Bool           -- ^ Enable evacuation mode
124
  , optExInst      :: [String]       -- ^ Instances to be excluded
125
  , optExTags      :: Maybe [String] -- ^ Tags to use for exclusion
126
  , optExecJobs    :: Bool           -- ^ Execute the commands via Luxi
127
  , optForce       :: Bool           -- ^ Force the execution
128
  , optGroup       :: Maybe GroupID  -- ^ The UUID of the group to process
129
  , optIAllocSrc   :: Maybe FilePath -- ^ The iallocation spec
130
  , optIgnoreNonRedundant :: Bool    -- ^ Ignore non-redundant instances
131
  , optSelInst     :: [String]       -- ^ Instances to be excluded
132
  , optLuxi        :: Maybe FilePath -- ^ Collect data from Luxi
133
  , optJobDelay    :: Double         -- ^ Delay before executing first job
134
  , optMachineReadable :: Bool       -- ^ Output machine-readable format
135
  , optMaster      :: String         -- ^ Collect data from RAPI
136
  , optMaxLength   :: Int            -- ^ Stop after this many steps
137
  , optMcpu        :: Maybe Double   -- ^ Override max cpu ratio for nodes
138
  , optMdsk        :: Double         -- ^ Max disk usage ratio for nodes
139
  , optMinGain     :: Score          -- ^ Min gain we aim for in a step
140
  , optMinGainLim  :: Score          -- ^ Limit below which we apply mingain
141
  , optMinScore    :: Score          -- ^ The minimum score we aim for
142
  , optNoHeaders   :: Bool           -- ^ Do not show a header line
143
  , optNoSimulation :: Bool          -- ^ Skip the rebalancing dry-run
144
  , optNodeSim     :: [String]       -- ^ Cluster simulation mode
145
  , optNodeTags    :: Maybe [String] -- ^ List of node tags to restrict to 
146
  , optOffline     :: [String]       -- ^ Names of offline nodes
147
  , optOfflineMaintenance :: Bool    -- ^ Pretend all instances are offline
148
  , optOneStepOnly :: Bool           -- ^ Only do the first step
149
  , optOutPath     :: FilePath       -- ^ Path to the output directory
150
  , optPrintMoves  :: Bool           -- ^ Whether to show the instance moves
151
  , optSaveCluster :: Maybe FilePath -- ^ Save cluster state to this file
152
  , optShowCmds    :: Maybe FilePath -- ^ Whether to show the command list
153
  , optShowHelp    :: Bool           -- ^ Just show the help
154
  , optShowComp    :: Bool           -- ^ Just show the completion info
155
  , optShowInsts   :: Bool           -- ^ Whether to show the instance map
156
  , optShowNodes   :: Maybe [String] -- ^ Whether to show node status
157
  , optShowVer     :: Bool           -- ^ Just show the program version
158
  , optSkipNonRedundant :: Bool      -- ^ Skip nodes with non-redundant instance
159
  , optStdSpec     :: Maybe RSpec    -- ^ Requested standard specs
160
  , optTestCount   :: Maybe Int      -- ^ Optional test count override
161
  , optTieredSpec  :: Maybe RSpec    -- ^ Requested specs for tiered mode
162
  , optReplay      :: Maybe String   -- ^ Unittests: RNG state
163
  , optVerbose     :: Int            -- ^ Verbosity level
164
  , optPriority    :: Maybe OpSubmitPriority -- ^ OpCode submit priority
165
  } deriving Show
166

    
167
-- | Default values for the command line options.
168
defaultOptions :: Options
169
defaultOptions  = Options
170
  { optDataFile    = Nothing
171
  , optDiskMoves   = True
172
  , optInstMoves   = True
173
  , optDiskTemplate = Nothing
174
  , optSpindleUse  = Nothing
175
  , optDynuFile    = Nothing
176
  , optEvacMode    = False
177
  , optExInst      = []
178
  , optExTags      = Nothing
179
  , optExecJobs    = False
180
  , optForce       = False
181
  , optGroup       = Nothing
182
  , optIAllocSrc   = Nothing
183
  , optIgnoreNonRedundant = False
184
  , optSelInst     = []
185
  , optLuxi        = Nothing
186
  , optJobDelay    = 10
187
  , optMachineReadable = False
188
  , optMaster      = ""
189
  , optMaxLength   = -1
190
  , optMcpu        = Nothing
191
  , optMdsk        = defReservedDiskRatio
192
  , optMinGain     = 1e-2
193
  , optMinGainLim  = 1e-1
194
  , optMinScore    = 1e-9
195
  , optNoHeaders   = False
196
  , optNoSimulation = False
197
  , optNodeSim     = []
198
  , optNodeTags    = Nothing
199
  , optSkipNonRedundant = False
200
  , optOffline     = []
201
  , optOfflineMaintenance = False
202
  , optOneStepOnly = False
203
  , optOutPath     = "."
204
  , optPrintMoves  = False
205
  , optSaveCluster = Nothing
206
  , optShowCmds    = Nothing
207
  , optShowHelp    = False
208
  , optShowComp    = False
209
  , optShowInsts   = False
210
  , optShowNodes   = Nothing
211
  , optShowVer     = False
212
  , optStdSpec     = Nothing
213
  , optTestCount   = Nothing
214
  , optTieredSpec  = Nothing
215
  , optReplay      = Nothing
216
  , optVerbose     = 1
217
  , optPriority    = Nothing
218
  }
219

    
220
-- | Abbreviation for the option type.
221
type OptType = GenericOptType Options
222

    
223
instance StandardOptions Options where
224
  helpRequested = optShowHelp
225
  verRequested  = optShowVer
226
  compRequested = optShowComp
227
  requestHelp o = o { optShowHelp = True }
228
  requestVer  o = o { optShowVer  = True }
229
  requestComp o = o { optShowComp = True }
230

    
231
-- * Helper functions
232

    
233
parseISpecString :: String -> String -> Result RSpec
234
parseISpecString descr inp = do
235
  let sp = sepSplit ',' inp
236
      err = Bad ("Invalid " ++ descr ++ " specification: '" ++ inp ++
237
                 "', expected disk,ram,cpu")
238
  when (length sp < 3 || length sp > 4) err
239
  prs <- mapM (\(fn, val) -> fn val) $
240
         zip [ annotateResult (descr ++ " specs disk") . parseUnit
241
             , annotateResult (descr ++ " specs memory") . parseUnit
242
             , tryRead (descr ++ " specs cpus")
243
             , tryRead (descr ++ " specs spindles")
244
             ] sp
245
  case prs of
246
    {- Spindles are optional, so that they are not needed when exclusive storage
247
       is disabled. When exclusive storage is disabled, spindles are ignored,
248
       so the actual value doesn't matter. We use 1 as a default so that in
249
       case someone forgets and exclusive storage is enabled, we don't run into
250
       weird situations. -}
251
    [dsk, ram, cpu] -> return $ RSpec cpu ram dsk 1
252
    [dsk, ram, cpu, spn] -> return $ RSpec cpu ram dsk spn
253
    _ -> err
254

    
255
-- | Disk template choices.
256
optComplDiskTemplate :: OptCompletion
257
optComplDiskTemplate = OptComplChoices $
258
                       map diskTemplateToRaw [minBound..maxBound]
259

    
260
-- * Command line options
261

    
262
oDataFile :: OptType
263
oDataFile =
264
  (Option "t" ["text-data"]
265
   (ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
266
   "the cluster data FILE",
267
   OptComplFile)
268

    
269
oDiskMoves :: OptType
270
oDiskMoves =
271
  (Option "" ["no-disk-moves"]
272
   (NoArg (\ opts -> Ok opts { optDiskMoves = False}))
273
   "disallow disk moves from the list of allowed instance changes,\
274
   \ thus allowing only the 'cheap' failover/migrate operations",
275
   OptComplNone)
276

    
277
oDiskTemplate :: OptType
278
oDiskTemplate =
279
  (Option "" ["disk-template"]
280
   (reqWithConversion diskTemplateFromRaw
281
    (\dt opts -> Ok opts { optDiskTemplate = Just dt })
282
    "TEMPLATE") "select the desired disk template",
283
   optComplDiskTemplate)
284

    
285
oSpindleUse :: OptType
286
oSpindleUse =
287
  (Option "" ["spindle-use"]
288
   (reqWithConversion (tryRead "parsing spindle-use")
289
    (\su opts -> do
290
       when (su < 0) $
291
            fail "Invalid value of the spindle-use (expected >= 0)"
292
       return $ opts { optSpindleUse = Just su })
293
    "SPINDLES") "select how many virtual spindle instances use\
294
                \ [default read from cluster]",
295
   OptComplFloat)
296

    
297
oSelInst :: OptType
298
oSelInst =
299
  (Option "" ["select-instances"]
300
   (ReqArg (\ f opts -> Ok opts { optSelInst = sepSplit ',' f }) "INSTS")
301
   "only select given instances for any moves",
302
   OptComplManyInstances)
303

    
304
oInstMoves :: OptType
305
oInstMoves =
306
  (Option "" ["no-instance-moves"]
307
   (NoArg (\ opts -> Ok opts { optInstMoves = False}))
308
   "disallow instance (primary node) moves from the list of allowed,\
309
   \ instance changes, thus allowing only slower, but sometimes\
310
   \ safer, drbd secondary changes",
311
   OptComplNone)
312

    
313
oDynuFile :: OptType
314
oDynuFile =
315
  (Option "U" ["dynu-file"]
316
   (ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
317
   "Import dynamic utilisation data from the given FILE",
318
   OptComplFile)
319

    
320
oEvacMode :: OptType
321
oEvacMode =
322
  (Option "E" ["evac-mode"]
323
   (NoArg (\opts -> Ok opts { optEvacMode = True }))
324
   "enable evacuation mode, where the algorithm only moves\
325
   \ instances away from offline and drained nodes",
326
   OptComplNone)
327

    
328
oExInst :: OptType
329
oExInst =
330
  (Option "" ["exclude-instances"]
331
   (ReqArg (\ f opts -> Ok opts { optExInst = sepSplit ',' f }) "INSTS")
332
   "exclude given instances from any moves",
333
   OptComplManyInstances)
334

    
335
oExTags :: OptType
336
oExTags =
337
  (Option "" ["exclusion-tags"]
338
   (ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
339
    "TAG,...") "Enable instance exclusion based on given tag prefix",
340
   OptComplString)
341

    
342
oExecJobs :: OptType
343
oExecJobs =
344
  (Option "X" ["exec"]
345
   (NoArg (\ opts -> Ok opts { optExecJobs = True}))
346
   "execute the suggested moves via Luxi (only available when using\
347
   \ it for data gathering)",
348
   OptComplNone)
349

    
350
oForce :: OptType
351
oForce =
352
  (Option "f" ["force"]
353
   (NoArg (\ opts -> Ok opts {optForce = True}))
354
   "force the execution of this program, even if warnings would\
355
   \ otherwise prevent it",
356
   OptComplNone)
357

    
358
oGroup :: OptType
359
oGroup =
360
  (Option "G" ["group"]
361
   (ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
362
   "the target node group (name or UUID)",
363
   OptComplOneGroup)
364

    
365
oIAllocSrc :: OptType
366
oIAllocSrc =
367
  (Option "I" ["ialloc-src"]
368
   (ReqArg (\ f opts -> Ok opts { optIAllocSrc = Just f }) "FILE")
369
   "Specify an iallocator spec as the cluster data source",
370
   OptComplFile)
371

    
372
oIgnoreNonRedundant :: OptType
373
oIgnoreNonRedundant =
374
  (Option "" ["ignore-non-redundant"]
375
   (NoArg (\ opts -> Ok opts { optIgnoreNonRedundant = True }))
376
    "Pretend that there are no non-redundant instances in the cluster",
377
    OptComplNone)
378

    
379
oJobDelay :: OptType
380
oJobDelay =
381
  (Option "" ["job-delay"]
382
   (reqWithConversion (tryRead "job delay")
383
    (\d opts -> Ok opts { optJobDelay = d }) "SECONDS")
384
   "insert this much delay before the execution of repair jobs\
385
   \ to allow the tool to continue processing instances",
386
   OptComplFloat)
387

    
388
genOLuxiSocket :: String -> OptType
389
genOLuxiSocket defSocket =
390
  (Option "L" ["luxi"]
391
   (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
392
            fromMaybe defSocket) "SOCKET")
393
   ("collect data via Luxi, optionally using the given SOCKET path [" ++
394
    defSocket ++ "]"),
395
   OptComplFile)
396

    
397
oLuxiSocket :: IO OptType
398
oLuxiSocket = liftM genOLuxiSocket Path.defaultLuxiSocket
399

    
400
oMachineReadable :: OptType
401
oMachineReadable =
402
  (Option "" ["machine-readable"]
403
   (OptArg (\ f opts -> do
404
              flag <- parseYesNo True f
405
              return $ opts { optMachineReadable = flag }) "CHOICE")
406
   "enable machine readable output (pass either 'yes' or 'no' to\
407
   \ explicitly control the flag, or without an argument defaults to\
408
   \ yes",
409
   optComplYesNo)
410

    
411
oMaxCpu :: OptType
412
oMaxCpu =
413
  (Option "" ["max-cpu"]
414
   (reqWithConversion (tryRead "parsing max-cpu")
415
    (\mcpu opts -> do
416
       when (mcpu <= 0) $
417
            fail "Invalid value of the max-cpu ratio, expected >0"
418
       return $ opts { optMcpu = Just mcpu }) "RATIO")
419
   "maximum virtual-to-physical cpu ratio for nodes (from 0\
420
   \ upwards) [default read from cluster]",
421
   OptComplFloat)
422

    
423
oMaxSolLength :: OptType
424
oMaxSolLength =
425
  (Option "l" ["max-length"]
426
   (reqWithConversion (tryRead "max solution length")
427
    (\i opts -> Ok opts { optMaxLength = i }) "N")
428
   "cap the solution at this many balancing or allocation\
429
   \ rounds (useful for very unbalanced clusters or empty\
430
   \ clusters)",
431
   OptComplInteger)
432

    
433
oMinDisk :: OptType
434
oMinDisk =
435
  (Option "" ["min-disk"]
436
   (reqWithConversion (tryRead "min free disk space")
437
    (\n opts -> Ok opts { optMdsk = n }) "RATIO")
438
   "minimum free disk space for nodes (between 0 and 1) [0]",
439
   OptComplFloat)
440

    
441
oMinGain :: OptType
442
oMinGain =
443
  (Option "g" ["min-gain"]
444
   (reqWithConversion (tryRead "min gain")
445
    (\g opts -> Ok opts { optMinGain = g }) "DELTA")
446
   "minimum gain to aim for in a balancing step before giving up",
447
   OptComplFloat)
448

    
449
oMinGainLim :: OptType
450
oMinGainLim =
451
  (Option "" ["min-gain-limit"]
452
   (reqWithConversion (tryRead "min gain limit")
453
    (\g opts -> Ok opts { optMinGainLim = g }) "SCORE")
454
   "minimum cluster score for which we start checking the min-gain",
455
   OptComplFloat)
456

    
457
oMinScore :: OptType
458
oMinScore =
459
  (Option "e" ["min-score"]
460
   (reqWithConversion (tryRead "min score")
461
    (\e opts -> Ok opts { optMinScore = e }) "EPSILON")
462
   "mininum score to aim for",
463
   OptComplFloat)
464

    
465
oNoHeaders :: OptType
466
oNoHeaders =
467
  (Option "" ["no-headers"]
468
   (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
469
   "do not show a header line",
470
   OptComplNone)
471

    
472
oNoSimulation :: OptType
473
oNoSimulation =
474
  (Option "" ["no-simulation"]
475
   (NoArg (\opts -> Ok opts {optNoSimulation = True}))
476
   "do not perform rebalancing simulation",
477
   OptComplNone)
478

    
479
oNodeSim :: OptType
480
oNodeSim =
481
  (Option "" ["simulate"]
482
   (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
483
   "simulate an empty cluster, given as\
484
   \ 'alloc_policy,num_nodes,disk,ram,cpu'",
485
   OptComplString)
486

    
487
oNodeTags :: OptType
488
oNodeTags =
489
  (Option "" ["node-tags"]
490
   (ReqArg (\ f opts -> Ok opts { optNodeTags = Just $ sepSplit ',' f })
491
    "TAG,...") "Restrict to nodes with the given tags",
492
   OptComplString)
493
     
494
oOfflineMaintenance :: OptType
495
oOfflineMaintenance =
496
  (Option "" ["offline-maintenance"]
497
   (NoArg (\ opts -> Ok opts {optOfflineMaintenance = True}))
498
   "Schedule offline maintenance, i.e., pretend that all instance are\
499
   \ offline.",
500
   OptComplNone)
501

    
502
oOfflineNode :: OptType
503
oOfflineNode =
504
  (Option "O" ["offline"]
505
   (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
506
   "set node as offline",
507
   OptComplOneNode)
508

    
509
oOneStepOnly :: OptType
510
oOneStepOnly =
511
  (Option "" ["one-step-only"]
512
   (NoArg (\ opts -> Ok opts {optOneStepOnly = True}))
513
   "Only do the first step",
514
   OptComplNone)
515

    
516
oOutputDir :: OptType
517
oOutputDir =
518
  (Option "d" ["output-dir"]
519
   (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
520
   "directory in which to write output files",
521
   OptComplDir)
522

    
523
oPrintCommands :: OptType
524
oPrintCommands =
525
  (Option "C" ["print-commands"]
526
   (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
527
            fromMaybe "-")
528
    "FILE")
529
   "print the ganeti command list for reaching the solution,\
530
   \ if an argument is passed then write the commands to a\
531
   \ file named as such",
532
   OptComplNone)
533

    
534
oPrintInsts :: OptType
535
oPrintInsts =
536
  (Option "" ["print-instances"]
537
   (NoArg (\ opts -> Ok opts { optShowInsts = True }))
538
   "print the final instance map",
539
   OptComplNone)
540

    
541
oPrintMoves :: OptType
542
oPrintMoves =
543
  (Option "" ["print-moves"]
544
   (NoArg (\ opts -> Ok opts { optPrintMoves = True }))
545
   "print the moves of the instances",
546
   OptComplNone)
547

    
548
oPrintNodes :: OptType
549
oPrintNodes =
550
  (Option "p" ["print-nodes"]
551
   (OptArg ((\ f opts ->
552
               let (prefix, realf) = case f of
553
                                       '+':rest -> (["+"], rest)
554
                                       _ -> ([], f)
555
                   splitted = prefix ++ sepSplit ',' realf
556
               in Ok opts { optShowNodes = Just splitted }) .
557
            fromMaybe []) "FIELDS")
558
   "print the final node list",
559
   OptComplNone)
560

    
561
oQuiet :: OptType
562
oQuiet =
563
  (Option "q" ["quiet"]
564
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
565
   "decrease the verbosity level",
566
   OptComplNone)
567

    
568
oRapiMaster :: OptType
569
oRapiMaster =
570
  (Option "m" ["master"]
571
   (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
572
   "collect data via RAPI at the given ADDRESS",
573
   OptComplHost)
574

    
575
oSaveCluster :: OptType
576
oSaveCluster =
577
  (Option "S" ["save"]
578
   (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
579
   "Save cluster state at the end of the processing to FILE",
580
   OptComplNone)
581

    
582
oSkipNonRedundant :: OptType
583
oSkipNonRedundant =
584
  (Option "" ["skip-non-redundant"]
585
   (NoArg (\ opts -> Ok opts { optSkipNonRedundant = True }))
586
    "Skip nodes that host a non-redundant instance",
587
    OptComplNone)
588

    
589
oStdSpec :: OptType
590
oStdSpec =
591
  (Option "" ["standard-alloc"]
592
   (ReqArg (\ inp opts -> do
593
              tspec <- parseISpecString "standard" inp
594
              return $ opts { optStdSpec = Just tspec } )
595
    "STDSPEC")
596
   "enable standard specs allocation, given as 'disk,ram,cpu'",
597
   OptComplString)
598

    
599
oTieredSpec :: OptType
600
oTieredSpec =
601
  (Option "" ["tiered-alloc"]
602
   (ReqArg (\ inp opts -> do
603
              tspec <- parseISpecString "tiered" inp
604
              return $ opts { optTieredSpec = Just tspec } )
605
    "TSPEC")
606
   "enable tiered specs allocation, given as 'disk,ram,cpu'",
607
   OptComplString)
608

    
609
oVerbose :: OptType
610
oVerbose =
611
  (Option "v" ["verbose"]
612
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
613
   "increase the verbosity level",
614
   OptComplNone)
615

    
616
oPriority :: OptType
617
oPriority =
618
  (Option "" ["priority"]
619
   (ReqArg (\ inp opts -> do
620
              prio <- parseSubmitPriority inp
621
              Ok opts { optPriority = Just prio }) "PRIO")
622
   "set the priority of submitted jobs",
623
    OptComplChoices (map fmtSubmitPriority [minBound..maxBound]))
624

    
625
-- | Generic options.
626
genericOpts :: [GenericOptType Options]
627
genericOpts =  [ oShowVer
628
               , oShowHelp
629
               , oShowComp
630
               ]
631

    
632
-- * Functions
633

    
634
-- | Wrapper over 'Common.parseOpts' with our custom options.
635
parseOpts :: [String]               -- ^ The command line arguments
636
          -> String                 -- ^ The program name
637
          -> [OptType]              -- ^ The supported command line options
638
          -> [ArgCompletion]        -- ^ The supported command line arguments
639
          -> IO (Options, [String]) -- ^ The resulting options and leftover
640
                                    -- arguments
641
parseOpts = Common.parseOpts defaultOptions
642

    
643

    
644
-- | A shell script template for autogenerated scripts.
645
shTemplate :: String
646
shTemplate =
647
  printf "#!/bin/sh\n\n\
648
         \# Auto-generated script for executing cluster rebalancing\n\n\
649
         \# To stop, touch the file /tmp/stop-htools\n\n\
650
         \set -e\n\n\
651
         \check() {\n\
652
         \  if [ -f /tmp/stop-htools ]; then\n\
653
         \    echo 'Stop requested, exiting'\n\
654
         \    exit 0\n\
655
         \  fi\n\
656
         \}\n\n"
657

    
658
-- | Optionally print the node list.
659
maybePrintNodes :: Maybe [String]       -- ^ The field list
660
                -> String               -- ^ Informational message
661
                -> ([String] -> String) -- ^ Function to generate the listing
662
                -> IO ()
663
maybePrintNodes Nothing _ _ = return ()
664
maybePrintNodes (Just fields) msg fn = do
665
  hPutStrLn stderr ""
666
  hPutStrLn stderr (msg ++ " status:")
667
  hPutStrLn stderr $ fn fields
668

    
669
-- | Optionally print the instance list.
670
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
671
                -> String -- ^ Type of the instance map (e.g. initial)
672
                -> String -- ^ The instance data
673
                -> IO ()
674
maybePrintInsts do_print msg instdata =
675
  when do_print $ do
676
    hPutStrLn stderr ""
677
    hPutStrLn stderr $ msg ++ " instance map:"
678
    hPutStr stderr instdata
679

    
680
-- | Function to display warning messages from parsing the cluster
681
-- state.
682
maybeShowWarnings :: [String] -- ^ The warning messages
683
                  -> IO ()
684
maybeShowWarnings fix_msgs =
685
  unless (null fix_msgs) $ do
686
    hPutStrLn stderr "Warning: cluster has inconsistent data:"
687
    hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
688

    
689
-- | Format a list of key, value as a shell fragment.
690
printKeys :: String              -- ^ Prefix to printed variables
691
          -> [(String, String)]  -- ^ List of (key, value) pairs to be printed
692
          -> IO ()
693
printKeys prefix =
694
  mapM_ (\(k, v) ->
695
           printf "%s_%s=%s\n" prefix (map toUpper k) (ensureQuoted v))
696

    
697
-- | Prints the final @OK@ marker in machine readable output.
698
printFinal :: String    -- ^ Prefix to printed variable
699
           -> Bool      -- ^ Whether output should be machine readable;
700
                        -- note: if not, there is nothing to print
701
           -> IO ()
702
printFinal prefix True =
703
  -- this should be the final entry
704
  printKeys prefix [("OK", "1")]
705

    
706
printFinal _ False = return ()
707

    
708
-- | Potentially set the node as offline based on passed offline list.
709
setNodeOffline :: [Ndx] -> Node.Node -> Node.Node
710
setNodeOffline offline_indices n =
711
  if Node.idx n `elem` offline_indices
712
    then Node.setOffline n True
713
    else n
714

    
715
-- | Set node properties based on command line options.
716
setNodeStatus :: Options -> Node.List -> IO Node.List
717
setNodeStatus opts fixed_nl = do
718
  let offline_passed = optOffline opts
719
      all_nodes = Container.elems fixed_nl
720
      offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
721
      offline_wrong = filter (not . goodLookupResult) offline_lkp
722
      offline_names = map lrContent offline_lkp
723
      offline_indices = map Node.idx $
724
                        filter (\n -> Node.name n `elem` offline_names)
725
                               all_nodes
726
      m_cpu = optMcpu opts
727
      m_dsk = optMdsk opts
728

    
729
  unless (null offline_wrong) .
730
         exitErr $ printf "wrong node name(s) set as offline: %s\n"
731
                   (commaJoin (map lrContent offline_wrong))
732
  let setMCpuFn = case m_cpu of
733
                    Nothing -> id
734
                    Just new_mcpu -> flip Node.setMcpu new_mcpu
735
  let nm = Container.map (setNodeOffline offline_indices .
736
                          flip Node.setMdsk m_dsk .
737
                          setMCpuFn) fixed_nl
738
  return nm