Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / CLI.hs @ 8af72964

History | View | Annotate | Download (20.6 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 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
  , genericOpts
87
  ) where
88

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

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

    
104
-- * Data types
105

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

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

    
195
-- | Abbreviation for the option type.
196
type OptType = GenericOptType Options
197

    
198
instance StandardOptions Options where
199
  helpRequested = optShowHelp
200
  verRequested  = optShowVer
201
  compRequested = optShowComp
202
  requestHelp o = o { optShowHelp = True }
203
  requestVer  o = o { optShowVer  = True }
204
  requestComp o = o { optShowComp = True }
205

    
206
-- * Helper functions
207

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

    
223
-- | Disk template choices.
224
optComplDiskTemplate :: OptCompletion
225
optComplDiskTemplate = OptComplChoices $
226
                       map diskTemplateToRaw [minBound..maxBound]
227

    
228
-- * Command line options
229

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

    
350
oLuxiSocket :: IO OptType
351
oLuxiSocket = liftM genOLuxiSocket Path.defaultLuxiSocket
352

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

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

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

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

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

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

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

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

    
425
oNoSimulation :: OptType
426
oNoSimulation =
427
  (Option "" ["no-simulation"]
428
   (NoArg (\opts -> Ok opts {optNoSimulation = True}))
429
   "do not perform rebalancing simulation",
430
   OptComplNone)
431

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

    
440
oOfflineNode :: OptType
441
oOfflineNode =
442
  (Option "O" ["offline"]
443
   (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
444
   "set node as offline",
445
   OptComplOneNode)
446

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

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

    
465
oPrintInsts :: OptType
466
oPrintInsts =
467
  (Option "" ["print-instances"]
468
   (NoArg (\ opts -> Ok opts { optShowInsts = True }))
469
   "print the final instance map",
470
   OptComplNone)
471

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

    
485
oQuiet :: OptType
486
oQuiet =
487
  (Option "q" ["quiet"]
488
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
489
   "decrease the verbosity level",
490
   OptComplNone)
491

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

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

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

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

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

    
533
-- | Generic options.
534
genericOpts :: [GenericOptType Options]
535
genericOpts =  [ oShowVer
536
               , oShowHelp
537
               , oShowComp
538
               ]
539

    
540
-- * Functions
541

    
542
-- | Wrapper over 'Common.parseOpts' with our custom options.
543
parseOpts :: [String]               -- ^ The command line arguments
544
          -> String                 -- ^ The program name
545
          -> [OptType]              -- ^ The supported command line options
546
          -> [ArgCompletion]        -- ^ The supported command line arguments
547
          -> IO (Options, [String]) -- ^ The resulting options and leftover
548
                                    -- arguments
549
parseOpts = Common.parseOpts defaultOptions
550

    
551

    
552
-- | A shell script template for autogenerated scripts.
553
shTemplate :: String
554
shTemplate =
555
  printf "#!/bin/sh\n\n\
556
         \# Auto-generated script for executing cluster rebalancing\n\n\
557
         \# To stop, touch the file /tmp/stop-htools\n\n\
558
         \set -e\n\n\
559
         \check() {\n\
560
         \  if [ -f /tmp/stop-htools ]; then\n\
561
         \    echo 'Stop requested, exiting'\n\
562
         \    exit 0\n\
563
         \  fi\n\
564
         \}\n\n"
565

    
566
-- | Optionally print the node list.
567
maybePrintNodes :: Maybe [String]       -- ^ The field list
568
                -> String               -- ^ Informational message
569
                -> ([String] -> String) -- ^ Function to generate the listing
570
                -> IO ()
571
maybePrintNodes Nothing _ _ = return ()
572
maybePrintNodes (Just fields) msg fn = do
573
  hPutStrLn stderr ""
574
  hPutStrLn stderr (msg ++ " status:")
575
  hPutStrLn stderr $ fn fields
576

    
577
-- | Optionally print the instance list.
578
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
579
                -> String -- ^ Type of the instance map (e.g. initial)
580
                -> String -- ^ The instance data
581
                -> IO ()
582
maybePrintInsts do_print msg instdata =
583
  when do_print $ do
584
    hPutStrLn stderr ""
585
    hPutStrLn stderr $ msg ++ " instance map:"
586
    hPutStr stderr instdata
587

    
588
-- | Function to display warning messages from parsing the cluster
589
-- state.
590
maybeShowWarnings :: [String] -- ^ The warning messages
591
                  -> IO ()
592
maybeShowWarnings fix_msgs =
593
  unless (null fix_msgs) $ do
594
    hPutStrLn stderr "Warning: cluster has inconsistent data:"
595
    hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
596

    
597
-- | Format a list of key, value as a shell fragment.
598
printKeys :: String              -- ^ Prefix to printed variables
599
          -> [(String, String)]  -- ^ List of (key, value) pairs to be printed
600
          -> IO ()
601
printKeys prefix =
602
  mapM_ (\(k, v) ->
603
           printf "%s_%s=%s\n" prefix (map toUpper k) (ensureQuoted v))
604

    
605
-- | Prints the final @OK@ marker in machine readable output.
606
printFinal :: String    -- ^ Prefix to printed variable
607
           -> Bool      -- ^ Whether output should be machine readable;
608
                        -- note: if not, there is nothing to print
609
           -> IO ()
610
printFinal prefix True =
611
  -- this should be the final entry
612
  printKeys prefix [("OK", "1")]
613

    
614
printFinal _ False = return ()
615

    
616
-- | Potentially set the node as offline based on passed offline list.
617
setNodeOffline :: [Ndx] -> Node.Node -> Node.Node
618
setNodeOffline offline_indices n =
619
  if Node.idx n `elem` offline_indices
620
    then Node.setOffline n True
621
    else n
622

    
623
-- | Set node properties based on command line options.
624
setNodeStatus :: Options -> Node.List -> IO Node.List
625
setNodeStatus opts fixed_nl = do
626
  let offline_passed = optOffline opts
627
      all_nodes = Container.elems fixed_nl
628
      offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
629
      offline_wrong = filter (not . goodLookupResult) offline_lkp
630
      offline_names = map lrContent offline_lkp
631
      offline_indices = map Node.idx $
632
                        filter (\n -> Node.name n `elem` offline_names)
633
                               all_nodes
634
      m_cpu = optMcpu opts
635
      m_dsk = optMdsk opts
636

    
637
  unless (null offline_wrong) .
638
         exitErr $ printf "wrong node name(s) set as offline: %s\n"
639
                   (commaJoin (map lrContent offline_wrong))
640
  let setMCpuFn = case m_cpu of
641
                    Nothing -> id
642
                    Just new_mcpu -> flip Node.setMcpu new_mcpu
643
  let nm = Container.map (setNodeOffline offline_indices .
644
                          flip Node.setMdsk m_dsk .
645
                          setMCpuFn) fixed_nl
646
  return nm