Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / CLI.hs @ bf028b21

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

    
90
import Control.Monad
91
import Data.Char (toUpper)
92
import Data.Maybe (fromMaybe)
93
import System.Console.GetOpt
94
import System.IO
95
import Text.Printf (printf)
96

    
97
import qualified Ganeti.HTools.Container as Container
98
import qualified Ganeti.HTools.Node as Node
99
import qualified Ganeti.Path as Path
100
import Ganeti.HTools.Types
101
import Ganeti.BasicTypes
102
import Ganeti.Common as Common
103
import Ganeti.Types
104
import Ganeti.Utils
105

    
106
-- * Data types
107

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

    
153
-- | Default values for the command line options.
154
defaultOptions :: Options
155
defaultOptions  = Options
156
  { optDataFile    = Nothing
157
  , optDiskMoves   = True
158
  , optInstMoves   = True
159
  , optDiskTemplate = Nothing
160
  , optSpindleUse  = Nothing
161
  , optDynuFile    = Nothing
162
  , optEvacMode    = False
163
  , optExInst      = []
164
  , optExTags      = Nothing
165
  , optExecJobs    = False
166
  , optGroup       = Nothing
167
  , optIAllocSrc   = Nothing
168
  , optSelInst     = []
169
  , optLuxi        = Nothing
170
  , optJobDelay    = 10
171
  , optMachineReadable = False
172
  , optMaster      = ""
173
  , optMaxLength   = -1
174
  , optMcpu        = Nothing
175
  , optMdsk        = defReservedDiskRatio
176
  , optMinGain     = 1e-2
177
  , optMinGainLim  = 1e-1
178
  , optMinScore    = 1e-9
179
  , optNoHeaders   = False
180
  , optNoSimulation = False
181
  , optNodeSim     = []
182
  , optOffline     = []
183
  , optOutPath     = "."
184
  , optSaveCluster = Nothing
185
  , optShowCmds    = Nothing
186
  , optShowHelp    = False
187
  , optShowComp    = False
188
  , optShowInsts   = False
189
  , optShowNodes   = Nothing
190
  , optShowVer     = False
191
  , optStdSpec     = Nothing
192
  , optTestCount   = Nothing
193
  , optTieredSpec  = Nothing
194
  , optReplay      = Nothing
195
  , optVerbose     = 1
196
  , optPriority    = Nothing
197
  }
198

    
199
-- | Abbreviation for the option type.
200
type OptType = GenericOptType Options
201

    
202
instance StandardOptions Options where
203
  helpRequested = optShowHelp
204
  verRequested  = optShowVer
205
  compRequested = optShowComp
206
  requestHelp o = o { optShowHelp = True }
207
  requestVer  o = o { optShowVer  = True }
208
  requestComp o = o { optShowComp = True }
209

    
210
-- * Helper functions
211

    
212
parseISpecString :: String -> String -> Result RSpec
213
parseISpecString descr inp = do
214
  let sp = sepSplit ',' inp
215
      err = Bad ("Invalid " ++ descr ++ " specification: '" ++ inp ++
216
                 "', expected disk,ram,cpu")
217
  when (length sp /= 3) err
218
  prs <- mapM (\(fn, val) -> fn val) $
219
         zip [ annotateResult (descr ++ " specs disk") . parseUnit
220
             , annotateResult (descr ++ " specs memory") . parseUnit
221
             , tryRead (descr ++ " specs cpus")
222
             ] sp
223
  case prs of
224
    [dsk, ram, cpu] -> return $ RSpec cpu ram dsk
225
    _ -> err
226

    
227
-- | Disk template choices.
228
optComplDiskTemplate :: OptCompletion
229
optComplDiskTemplate = OptComplChoices $
230
                       map diskTemplateToRaw [minBound..maxBound]
231

    
232
-- * Command line options
233

    
234
oDataFile :: OptType
235
oDataFile =
236
  (Option "t" ["text-data"]
237
   (ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
238
   "the cluster data FILE",
239
   OptComplFile)
240

    
241
oDiskMoves :: OptType
242
oDiskMoves =
243
  (Option "" ["no-disk-moves"]
244
   (NoArg (\ opts -> Ok opts { optDiskMoves = False}))
245
   "disallow disk moves from the list of allowed instance changes,\
246
   \ thus allowing only the 'cheap' failover/migrate operations",
247
   OptComplNone)
248

    
249
oDiskTemplate :: OptType
250
oDiskTemplate =
251
  (Option "" ["disk-template"]
252
   (reqWithConversion diskTemplateFromRaw
253
    (\dt opts -> Ok opts { optDiskTemplate = Just dt })
254
    "TEMPLATE") "select the desired disk template",
255
   optComplDiskTemplate)
256

    
257
oSpindleUse :: OptType
258
oSpindleUse =
259
  (Option "" ["spindle-use"]
260
   (reqWithConversion (tryRead "parsing spindle-use")
261
    (\su opts -> do
262
       when (su < 0) $
263
            fail "Invalid value of the spindle-use (expected >= 0)"
264
       return $ opts { optSpindleUse = Just su })
265
    "SPINDLES") "select how many virtual spindle instances use\
266
                \ [default read from cluster]",
267
   OptComplFloat)
268

    
269
oSelInst :: OptType
270
oSelInst =
271
  (Option "" ["select-instances"]
272
   (ReqArg (\ f opts -> Ok opts { optSelInst = sepSplit ',' f }) "INSTS")
273
   "only select given instances for any moves",
274
   OptComplManyInstances)
275

    
276
oInstMoves :: OptType
277
oInstMoves =
278
  (Option "" ["no-instance-moves"]
279
   (NoArg (\ opts -> Ok opts { optInstMoves = False}))
280
   "disallow instance (primary node) moves from the list of allowed,\
281
   \ instance changes, thus allowing only slower, but sometimes\
282
   \ safer, drbd secondary changes",
283
   OptComplNone)
284

    
285
oDynuFile :: OptType
286
oDynuFile =
287
  (Option "U" ["dynu-file"]
288
   (ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
289
   "Import dynamic utilisation data from the given FILE",
290
   OptComplFile)
291

    
292
oEvacMode :: OptType
293
oEvacMode =
294
  (Option "E" ["evac-mode"]
295
   (NoArg (\opts -> Ok opts { optEvacMode = True }))
296
   "enable evacuation mode, where the algorithm only moves\
297
   \ instances away from offline and drained nodes",
298
   OptComplNone)
299

    
300
oExInst :: OptType
301
oExInst =
302
  (Option "" ["exclude-instances"]
303
   (ReqArg (\ f opts -> Ok opts { optExInst = sepSplit ',' f }) "INSTS")
304
   "exclude given instances from any moves",
305
   OptComplManyInstances)
306

    
307
oExTags :: OptType
308
oExTags =
309
  (Option "" ["exclusion-tags"]
310
   (ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
311
    "TAG,...") "Enable instance exclusion based on given tag prefix",
312
   OptComplString)
313

    
314
oExecJobs :: OptType
315
oExecJobs =
316
  (Option "X" ["exec"]
317
   (NoArg (\ opts -> Ok opts { optExecJobs = True}))
318
   "execute the suggested moves via Luxi (only available when using\
319
   \ it for data gathering)",
320
   OptComplNone)
321

    
322
oGroup :: OptType
323
oGroup =
324
  (Option "G" ["group"]
325
   (ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
326
   "the target node group (name or UUID)",
327
   OptComplOneGroup)
328

    
329
oIAllocSrc :: OptType
330
oIAllocSrc =
331
  (Option "I" ["ialloc-src"]
332
   (ReqArg (\ f opts -> Ok opts { optIAllocSrc = Just f }) "FILE")
333
   "Specify an iallocator spec as the cluster data source",
334
   OptComplFile)
335

    
336
oJobDelay :: OptType
337
oJobDelay =
338
  (Option "" ["job-delay"]
339
   (reqWithConversion (tryRead "job delay")
340
    (\d opts -> Ok opts { optJobDelay = d }) "SECONDS")
341
   "insert this much delay before the execution of repair jobs\
342
   \ to allow the tool to continue processing instances",
343
   OptComplFloat)
344

    
345
genOLuxiSocket :: String -> OptType
346
genOLuxiSocket defSocket =
347
  (Option "L" ["luxi"]
348
   (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
349
            fromMaybe defSocket) "SOCKET")
350
   ("collect data via Luxi, optionally using the given SOCKET path [" ++
351
    defSocket ++ "]"),
352
   OptComplFile)
353

    
354
oLuxiSocket :: IO OptType
355
oLuxiSocket = liftM genOLuxiSocket Path.defaultLuxiSocket
356

    
357
oMachineReadable :: OptType
358
oMachineReadable =
359
  (Option "" ["machine-readable"]
360
   (OptArg (\ f opts -> do
361
              flag <- parseYesNo True f
362
              return $ opts { optMachineReadable = flag }) "CHOICE")
363
   "enable machine readable output (pass either 'yes' or 'no' to\
364
   \ explicitly control the flag, or without an argument defaults to\
365
   \ yes",
366
   optComplYesNo)
367

    
368
oMaxCpu :: OptType
369
oMaxCpu =
370
  (Option "" ["max-cpu"]
371
   (reqWithConversion (tryRead "parsing max-cpu")
372
    (\mcpu opts -> do
373
       when (mcpu <= 0) $
374
            fail "Invalid value of the max-cpu ratio, expected >0"
375
       return $ opts { optMcpu = Just mcpu }) "RATIO")
376
   "maximum virtual-to-physical cpu ratio for nodes (from 0\
377
   \ upwards) [default read from cluster]",
378
   OptComplFloat)
379

    
380
oMaxSolLength :: OptType
381
oMaxSolLength =
382
  (Option "l" ["max-length"]
383
   (reqWithConversion (tryRead "max solution length")
384
    (\i opts -> Ok opts { optMaxLength = i }) "N")
385
   "cap the solution at this many balancing or allocation\
386
   \ rounds (useful for very unbalanced clusters or empty\
387
   \ clusters)",
388
   OptComplInteger)
389

    
390
oMinDisk :: OptType
391
oMinDisk =
392
  (Option "" ["min-disk"]
393
   (reqWithConversion (tryRead "min free disk space")
394
    (\n opts -> Ok opts { optMdsk = n }) "RATIO")
395
   "minimum free disk space for nodes (between 0 and 1) [0]",
396
   OptComplFloat)
397

    
398
oMinGain :: OptType
399
oMinGain =
400
  (Option "g" ["min-gain"]
401
   (reqWithConversion (tryRead "min gain")
402
    (\g opts -> Ok opts { optMinGain = g }) "DELTA")
403
   "minimum gain to aim for in a balancing step before giving up",
404
   OptComplFloat)
405

    
406
oMinGainLim :: OptType
407
oMinGainLim =
408
  (Option "" ["min-gain-limit"]
409
   (reqWithConversion (tryRead "min gain limit")
410
    (\g opts -> Ok opts { optMinGainLim = g }) "SCORE")
411
   "minimum cluster score for which we start checking the min-gain",
412
   OptComplFloat)
413

    
414
oMinScore :: OptType
415
oMinScore =
416
  (Option "e" ["min-score"]
417
   (reqWithConversion (tryRead "min score")
418
    (\e opts -> Ok opts { optMinScore = e }) "EPSILON")
419
   "mininum score to aim for",
420
   OptComplFloat)
421

    
422
oNoHeaders :: OptType
423
oNoHeaders =
424
  (Option "" ["no-headers"]
425
   (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
426
   "do not show a header line",
427
   OptComplNone)
428

    
429
oNoSimulation :: OptType
430
oNoSimulation =
431
  (Option "" ["no-simulation"]
432
   (NoArg (\opts -> Ok opts {optNoSimulation = True}))
433
   "do not perform rebalancing simulation",
434
   OptComplNone)
435

    
436
oNodeSim :: OptType
437
oNodeSim =
438
  (Option "" ["simulate"]
439
   (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
440
   "simulate an empty cluster, given as\
441
   \ 'alloc_policy,num_nodes,disk,ram,cpu'",
442
   OptComplString)
443

    
444
oOfflineNode :: OptType
445
oOfflineNode =
446
  (Option "O" ["offline"]
447
   (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
448
   "set node as offline",
449
   OptComplOneNode)
450

    
451
oOutputDir :: OptType
452
oOutputDir =
453
  (Option "d" ["output-dir"]
454
   (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
455
   "directory in which to write output files",
456
   OptComplDir)
457

    
458
oPrintCommands :: OptType
459
oPrintCommands =
460
  (Option "C" ["print-commands"]
461
   (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
462
            fromMaybe "-")
463
    "FILE")
464
   "print the ganeti command list for reaching the solution,\
465
   \ if an argument is passed then write the commands to a\
466
   \ file named as such",
467
   OptComplNone)
468

    
469
oPrintInsts :: OptType
470
oPrintInsts =
471
  (Option "" ["print-instances"]
472
   (NoArg (\ opts -> Ok opts { optShowInsts = True }))
473
   "print the final instance map",
474
   OptComplNone)
475

    
476
oPrintNodes :: OptType
477
oPrintNodes =
478
  (Option "p" ["print-nodes"]
479
   (OptArg ((\ f opts ->
480
               let (prefix, realf) = case f of
481
                                       '+':rest -> (["+"], rest)
482
                                       _ -> ([], f)
483
                   splitted = prefix ++ sepSplit ',' realf
484
               in Ok opts { optShowNodes = Just splitted }) .
485
            fromMaybe []) "FIELDS")
486
   "print the final node list",
487
   OptComplNone)
488

    
489
oQuiet :: OptType
490
oQuiet =
491
  (Option "q" ["quiet"]
492
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
493
   "decrease the verbosity level",
494
   OptComplNone)
495

    
496
oRapiMaster :: OptType
497
oRapiMaster =
498
  (Option "m" ["master"]
499
   (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
500
   "collect data via RAPI at the given ADDRESS",
501
   OptComplHost)
502

    
503
oSaveCluster :: OptType
504
oSaveCluster =
505
  (Option "S" ["save"]
506
   (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
507
   "Save cluster state at the end of the processing to FILE",
508
   OptComplNone)
509

    
510
oStdSpec :: OptType
511
oStdSpec =
512
  (Option "" ["standard-alloc"]
513
   (ReqArg (\ inp opts -> do
514
              tspec <- parseISpecString "standard" inp
515
              return $ opts { optStdSpec = Just tspec } )
516
    "STDSPEC")
517
   "enable standard specs allocation, given as 'disk,ram,cpu'",
518
   OptComplString)
519

    
520
oTieredSpec :: OptType
521
oTieredSpec =
522
  (Option "" ["tiered-alloc"]
523
   (ReqArg (\ inp opts -> do
524
              tspec <- parseISpecString "tiered" inp
525
              return $ opts { optTieredSpec = Just tspec } )
526
    "TSPEC")
527
   "enable tiered specs allocation, given as 'disk,ram,cpu'",
528
   OptComplString)
529

    
530
oVerbose :: OptType
531
oVerbose =
532
  (Option "v" ["verbose"]
533
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
534
   "increase the verbosity level",
535
   OptComplNone)
536

    
537
oPriority :: OptType
538
oPriority =
539
  (Option "" ["priority"]
540
   (ReqArg (\ inp opts -> do
541
              prio <- parseSubmitPriority inp
542
              Ok opts { optPriority = Just prio }) "PRIO")
543
   "set the priority of submitted jobs",
544
    OptComplChoices (map fmtSubmitPriority [minBound..maxBound]))
545

    
546
-- | Generic options.
547
genericOpts :: [GenericOptType Options]
548
genericOpts =  [ oShowVer
549
               , oShowHelp
550
               , oShowComp
551
               ]
552

    
553
-- * Functions
554

    
555
-- | Wrapper over 'Common.parseOpts' with our custom options.
556
parseOpts :: [String]               -- ^ The command line arguments
557
          -> String                 -- ^ The program name
558
          -> [OptType]              -- ^ The supported command line options
559
          -> [ArgCompletion]        -- ^ The supported command line arguments
560
          -> IO (Options, [String]) -- ^ The resulting options and leftover
561
                                    -- arguments
562
parseOpts = Common.parseOpts defaultOptions
563

    
564

    
565
-- | A shell script template for autogenerated scripts.
566
shTemplate :: String
567
shTemplate =
568
  printf "#!/bin/sh\n\n\
569
         \# Auto-generated script for executing cluster rebalancing\n\n\
570
         \# To stop, touch the file /tmp/stop-htools\n\n\
571
         \set -e\n\n\
572
         \check() {\n\
573
         \  if [ -f /tmp/stop-htools ]; then\n\
574
         \    echo 'Stop requested, exiting'\n\
575
         \    exit 0\n\
576
         \  fi\n\
577
         \}\n\n"
578

    
579
-- | Optionally print the node list.
580
maybePrintNodes :: Maybe [String]       -- ^ The field list
581
                -> String               -- ^ Informational message
582
                -> ([String] -> String) -- ^ Function to generate the listing
583
                -> IO ()
584
maybePrintNodes Nothing _ _ = return ()
585
maybePrintNodes (Just fields) msg fn = do
586
  hPutStrLn stderr ""
587
  hPutStrLn stderr (msg ++ " status:")
588
  hPutStrLn stderr $ fn fields
589

    
590
-- | Optionally print the instance list.
591
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
592
                -> String -- ^ Type of the instance map (e.g. initial)
593
                -> String -- ^ The instance data
594
                -> IO ()
595
maybePrintInsts do_print msg instdata =
596
  when do_print $ do
597
    hPutStrLn stderr ""
598
    hPutStrLn stderr $ msg ++ " instance map:"
599
    hPutStr stderr instdata
600

    
601
-- | Function to display warning messages from parsing the cluster
602
-- state.
603
maybeShowWarnings :: [String] -- ^ The warning messages
604
                  -> IO ()
605
maybeShowWarnings fix_msgs =
606
  unless (null fix_msgs) $ do
607
    hPutStrLn stderr "Warning: cluster has inconsistent data:"
608
    hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
609

    
610
-- | Format a list of key, value as a shell fragment.
611
printKeys :: String              -- ^ Prefix to printed variables
612
          -> [(String, String)]  -- ^ List of (key, value) pairs to be printed
613
          -> IO ()
614
printKeys prefix =
615
  mapM_ (\(k, v) ->
616
           printf "%s_%s=%s\n" prefix (map toUpper k) (ensureQuoted v))
617

    
618
-- | Prints the final @OK@ marker in machine readable output.
619
printFinal :: String    -- ^ Prefix to printed variable
620
           -> Bool      -- ^ Whether output should be machine readable;
621
                        -- note: if not, there is nothing to print
622
           -> IO ()
623
printFinal prefix True =
624
  -- this should be the final entry
625
  printKeys prefix [("OK", "1")]
626

    
627
printFinal _ False = return ()
628

    
629
-- | Potentially set the node as offline based on passed offline list.
630
setNodeOffline :: [Ndx] -> Node.Node -> Node.Node
631
setNodeOffline offline_indices n =
632
  if Node.idx n `elem` offline_indices
633
    then Node.setOffline n True
634
    else n
635

    
636
-- | Set node properties based on command line options.
637
setNodeStatus :: Options -> Node.List -> IO Node.List
638
setNodeStatus opts fixed_nl = do
639
  let offline_passed = optOffline opts
640
      all_nodes = Container.elems fixed_nl
641
      offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
642
      offline_wrong = filter (not . goodLookupResult) offline_lkp
643
      offline_names = map lrContent offline_lkp
644
      offline_indices = map Node.idx $
645
                        filter (\n -> Node.name n `elem` offline_names)
646
                               all_nodes
647
      m_cpu = optMcpu opts
648
      m_dsk = optMdsk opts
649

    
650
  unless (null offline_wrong) .
651
         exitErr $ printf "wrong node name(s) set as offline: %s\n"
652
                   (commaJoin (map lrContent offline_wrong))
653
  let setMCpuFn = case m_cpu of
654
                    Nothing -> id
655
                    Just new_mcpu -> flip Node.setMcpu new_mcpu
656
  let nm = Container.map (setNodeOffline offline_indices .
657
                          flip Node.setMdsk m_dsk .
658
                          setMCpuFn) fixed_nl
659
  return nm