Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / CLI.hs @ 3e02cd3c

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, 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
  , genOLuxiSocket
59
  , oLuxiSocket
60
  , oMachineReadable
61
  , oMaxCpu
62
  , oMaxSolLength
63
  , oMinDisk
64
  , oMinGain
65
  , oMinGainLim
66
  , oMinScore
67
  , oNoHeaders
68
  , oNoSimulation
69
  , oNodeSim
70
  , oOfflineNode
71
  , oOutputDir
72
  , oPrintCommands
73
  , oPrintInsts
74
  , oPrintNodes
75
  , oQuiet
76
  , oRapiMaster
77
  , oSaveCluster
78
  , oSelInst
79
  , oShowHelp
80
  , oShowVer
81
  , oShowComp
82
  , oStdSpec
83
  , oTieredSpec
84
  , oVerbose
85
  , oPriority
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.Types
103
import Ganeti.Utils
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 :: Maybe DiskTemplate  -- ^ Override for the disk template
113
  , optSpindleUse  :: Maybe Int      -- ^ Override for the spindle usage
114
  , optDynuFile    :: Maybe FilePath -- ^ Optional file with dynamic use data
115
  , optEvacMode    :: Bool           -- ^ Enable evacuation mode
116
  , optExInst      :: [String]       -- ^ Instances to be excluded
117
  , optExTags      :: Maybe [String] -- ^ Tags to use for exclusion
118
  , optExecJobs    :: Bool           -- ^ Execute the commands via Luxi
119
  , optGroup       :: Maybe GroupID  -- ^ The UUID of the group to process
120
  , optIAllocSrc   :: Maybe FilePath -- ^ The iallocation spec
121
  , optSelInst     :: [String]       -- ^ Instances to be excluded
122
  , optLuxi        :: Maybe FilePath -- ^ Collect data from Luxi
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
  , optPriority    :: Maybe OpSubmitPriority -- ^ OpCode submit priority
149
  } deriving Show
150

    
151
-- | Default values for the command line options.
152
defaultOptions :: Options
153
defaultOptions  = Options
154
  { optDataFile    = Nothing
155
  , optDiskMoves   = True
156
  , optInstMoves   = True
157
  , optDiskTemplate = Nothing
158
  , optSpindleUse  = Nothing
159
  , optDynuFile    = Nothing
160
  , optEvacMode    = False
161
  , optExInst      = []
162
  , optExTags      = Nothing
163
  , optExecJobs    = False
164
  , optGroup       = Nothing
165
  , optIAllocSrc   = Nothing
166
  , optSelInst     = []
167
  , optLuxi        = Nothing
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
  , optPriority    = Nothing
194
  }
195

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

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

    
207
-- * Helper functions
208

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

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

    
229
-- * Command line options
230

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

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

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

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

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

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

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

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

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

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

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

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

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

    
333
genOLuxiSocket :: String -> OptType
334
genOLuxiSocket defSocket =
335
  (Option "L" ["luxi"]
336
   (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
337
            fromMaybe defSocket) "SOCKET")
338
   ("collect data via Luxi, optionally using the given SOCKET path [" ++
339
    defSocket ++ "]"),
340
   OptComplFile)
341

    
342
oLuxiSocket :: IO OptType
343
oLuxiSocket = liftM genOLuxiSocket Path.defaultLuxiSocket
344

    
345
oMachineReadable :: OptType
346
oMachineReadable =
347
  (Option "" ["machine-readable"]
348
   (OptArg (\ f opts -> do
349
              flag <- parseYesNo True f
350
              return $ opts { optMachineReadable = flag }) "CHOICE")
351
   "enable machine readable output (pass either 'yes' or 'no' to\
352
   \ explicitly control the flag, or without an argument defaults to\
353
   \ yes",
354
   optComplYesNo)
355

    
356
oMaxCpu :: OptType
357
oMaxCpu =
358
  (Option "" ["max-cpu"]
359
   (reqWithConversion (tryRead "parsing max-cpu")
360
    (\mcpu opts -> do
361
       when (mcpu <= 0) $
362
            fail "Invalid value of the max-cpu ratio, expected >0"
363
       return $ opts { optMcpu = Just mcpu }) "RATIO")
364
   "maximum virtual-to-physical cpu ratio for nodes (from 0\
365
   \ upwards) [default read from cluster]",
366
   OptComplFloat)
367

    
368
oMaxSolLength :: OptType
369
oMaxSolLength =
370
  (Option "l" ["max-length"]
371
   (reqWithConversion (tryRead "max solution length")
372
    (\i opts -> Ok opts { optMaxLength = i }) "N")
373
   "cap the solution at this many balancing or allocation\
374
   \ rounds (useful for very unbalanced clusters or empty\
375
   \ clusters)",
376
   OptComplInteger)
377

    
378
oMinDisk :: OptType
379
oMinDisk =
380
  (Option "" ["min-disk"]
381
   (reqWithConversion (tryRead "min free disk space")
382
    (\n opts -> Ok opts { optMdsk = n }) "RATIO")
383
   "minimum free disk space for nodes (between 0 and 1) [0]",
384
   OptComplFloat)
385

    
386
oMinGain :: OptType
387
oMinGain =
388
  (Option "g" ["min-gain"]
389
   (reqWithConversion (tryRead "min gain")
390
    (\g opts -> Ok opts { optMinGain = g }) "DELTA")
391
   "minimum gain to aim for in a balancing step before giving up",
392
   OptComplFloat)
393

    
394
oMinGainLim :: OptType
395
oMinGainLim =
396
  (Option "" ["min-gain-limit"]
397
   (reqWithConversion (tryRead "min gain limit")
398
    (\g opts -> Ok opts { optMinGainLim = g }) "SCORE")
399
   "minimum cluster score for which we start checking the min-gain",
400
   OptComplFloat)
401

    
402
oMinScore :: OptType
403
oMinScore =
404
  (Option "e" ["min-score"]
405
   (reqWithConversion (tryRead "min score")
406
    (\e opts -> Ok opts { optMinScore = e }) "EPSILON")
407
   "mininum score to aim for",
408
   OptComplFloat)
409

    
410
oNoHeaders :: OptType
411
oNoHeaders =
412
  (Option "" ["no-headers"]
413
   (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
414
   "do not show a header line",
415
   OptComplNone)
416

    
417
oNoSimulation :: OptType
418
oNoSimulation =
419
  (Option "" ["no-simulation"]
420
   (NoArg (\opts -> Ok opts {optNoSimulation = True}))
421
   "do not perform rebalancing simulation",
422
   OptComplNone)
423

    
424
oNodeSim :: OptType
425
oNodeSim =
426
  (Option "" ["simulate"]
427
   (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
428
   "simulate an empty cluster, given as\
429
   \ 'alloc_policy,num_nodes,disk,ram,cpu'",
430
   OptComplString)
431

    
432
oOfflineNode :: OptType
433
oOfflineNode =
434
  (Option "O" ["offline"]
435
   (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
436
   "set node as offline",
437
   OptComplOneNode)
438

    
439
oOutputDir :: OptType
440
oOutputDir =
441
  (Option "d" ["output-dir"]
442
   (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
443
   "directory in which to write output files",
444
   OptComplDir)
445

    
446
oPrintCommands :: OptType
447
oPrintCommands =
448
  (Option "C" ["print-commands"]
449
   (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
450
            fromMaybe "-")
451
    "FILE")
452
   "print the ganeti command list for reaching the solution,\
453
   \ if an argument is passed then write the commands to a\
454
   \ file named as such",
455
   OptComplNone)
456

    
457
oPrintInsts :: OptType
458
oPrintInsts =
459
  (Option "" ["print-instances"]
460
   (NoArg (\ opts -> Ok opts { optShowInsts = True }))
461
   "print the final instance map",
462
   OptComplNone)
463

    
464
oPrintNodes :: OptType
465
oPrintNodes =
466
  (Option "p" ["print-nodes"]
467
   (OptArg ((\ f opts ->
468
               let (prefix, realf) = case f of
469
                                       '+':rest -> (["+"], rest)
470
                                       _ -> ([], f)
471
                   splitted = prefix ++ sepSplit ',' realf
472
               in Ok opts { optShowNodes = Just splitted }) .
473
            fromMaybe []) "FIELDS")
474
   "print the final node list",
475
   OptComplNone)
476

    
477
oQuiet :: OptType
478
oQuiet =
479
  (Option "q" ["quiet"]
480
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
481
   "decrease the verbosity level",
482
   OptComplNone)
483

    
484
oRapiMaster :: OptType
485
oRapiMaster =
486
  (Option "m" ["master"]
487
   (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
488
   "collect data via RAPI at the given ADDRESS",
489
   OptComplHost)
490

    
491
oSaveCluster :: OptType
492
oSaveCluster =
493
  (Option "S" ["save"]
494
   (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
495
   "Save cluster state at the end of the processing to FILE",
496
   OptComplNone)
497

    
498
oStdSpec :: OptType
499
oStdSpec =
500
  (Option "" ["standard-alloc"]
501
   (ReqArg (\ inp opts -> do
502
              tspec <- parseISpecString "standard" inp
503
              return $ opts { optStdSpec = Just tspec } )
504
    "STDSPEC")
505
   "enable standard specs allocation, given as 'disk,ram,cpu'",
506
   OptComplString)
507

    
508
oTieredSpec :: OptType
509
oTieredSpec =
510
  (Option "" ["tiered-alloc"]
511
   (ReqArg (\ inp opts -> do
512
              tspec <- parseISpecString "tiered" inp
513
              return $ opts { optTieredSpec = Just tspec } )
514
    "TSPEC")
515
   "enable tiered specs allocation, given as 'disk,ram,cpu'",
516
   OptComplString)
517

    
518
oVerbose :: OptType
519
oVerbose =
520
  (Option "v" ["verbose"]
521
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
522
   "increase the verbosity level",
523
   OptComplNone)
524

    
525
oPriority :: OptType
526
oPriority =
527
  (Option "" ["priority"]
528
   (ReqArg (\ inp opts -> do
529
              prio <- parseSubmitPriority inp
530
              Ok opts { optPriority = Just prio }) "PRIO")
531
   "set the priority of submitted jobs",
532
    OptComplChoices (map fmtSubmitPriority [minBound..maxBound]))
533

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

    
541
-- * Functions
542

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

    
552

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

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

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

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

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

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

    
615
printFinal _ False = return ()
616

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

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

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