Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ 26d62e4c

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

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

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

    
102
-- * Data types
103

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

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

    
191
-- | Abrreviation for the option type.
192
type OptType = GenericOptType Options
193

    
194
instance StandardOptions Options where
195
  helpRequested = optShowHelp
196
  verRequested  = optShowVer
197
  compRequested = optShowComp
198
  requestHelp o = o { optShowHelp = True }
199
  requestVer  o = o { optShowVer  = True }
200
  requestComp o = o { optShowComp = True }
201

    
202
-- * Helper functions
203

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

    
219
-- | Disk template choices.
220
optComplDiskTemplate :: OptCompletion
221
optComplDiskTemplate = OptComplChoices $
222
                       map diskTemplateToRaw [minBound..maxBound]
223

    
224
-- * Command line options
225

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

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

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

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

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

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

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

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

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

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

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

    
314
oGroup :: OptType
315
oGroup =
316
  (Option "G" ["group"]
317
   (ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
318
   "the ID of the group to balance",
319
   OptComplOneGroup)
320

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

    
328
oLuxiSocket :: OptType
329
oLuxiSocket =
330
  (Option "L" ["luxi"]
331
   (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
332
            fromMaybe Path.defaultLuxiSocket) "SOCKET")
333
   "collect data via Luxi, optionally using the given SOCKET path",
334
   OptComplFile)
335

    
336
oMachineReadable :: OptType
337
oMachineReadable =
338
  (Option "" ["machine-readable"]
339
   (OptArg (\ f opts -> do
340
              flag <- parseYesNo True f
341
              return $ opts { optMachineReadable = flag }) "CHOICE")
342
   "enable machine readable output (pass either 'yes' or 'no' to\
343
   \ explicitly control the flag, or without an argument defaults to\
344
   \ yes",
345
   optComplYesNo)
346

    
347
oMaxCpu :: OptType
348
oMaxCpu =
349
  (Option "" ["max-cpu"]
350
   (reqWithConversion (tryRead "parsing max-cpu")
351
    (\mcpu opts -> do
352
       when (mcpu <= 0) $
353
            fail "Invalid value of the max-cpu ratio, expected >0"
354
       return $ opts { optMcpu = Just mcpu }) "RATIO")
355
   "maximum virtual-to-physical cpu ratio for nodes (from 0\
356
   \ upwards) [default read from cluster]",
357
   OptComplNumeric)
358

    
359
oMaxSolLength :: OptType
360
oMaxSolLength =
361
  (Option "l" ["max-length"]
362
   (reqWithConversion (tryRead "max solution length")
363
    (\i opts -> Ok opts { optMaxLength = i }) "N")
364
   "cap the solution at this many balancing or allocation \
365
   \ rounds (useful for very unbalanced clusters or empty \
366
   \ clusters)",
367
   OptComplNumeric)
368

    
369
oMinDisk :: OptType
370
oMinDisk =
371
  (Option "" ["min-disk"]
372
   (reqWithConversion (tryRead "min free disk space")
373
    (\n opts -> Ok opts { optMdsk = n }) "RATIO")
374
   "minimum free disk space for nodes (between 0 and 1) [0]",
375
   OptComplNumeric)
376

    
377
oMinGain :: OptType
378
oMinGain =
379
  (Option "g" ["min-gain"]
380
   (reqWithConversion (tryRead "min gain")
381
    (\g opts -> Ok opts { optMinGain = g }) "DELTA")
382
   "minimum gain to aim for in a balancing step before giving up",
383
   OptComplNumeric)
384

    
385
oMinGainLim :: OptType
386
oMinGainLim =
387
  (Option "" ["min-gain-limit"]
388
   (reqWithConversion (tryRead "min gain limit")
389
    (\g opts -> Ok opts { optMinGainLim = g }) "SCORE")
390
   "minimum cluster score for which we start checking the min-gain",
391
   OptComplNumeric)
392

    
393
oMinScore :: OptType
394
oMinScore =
395
  (Option "e" ["min-score"]
396
   (reqWithConversion (tryRead "min score")
397
    (\e opts -> Ok opts { optMinScore = e }) "EPSILON")
398
   "mininum score to aim for",
399
   OptComplNumeric)
400

    
401
oNoHeaders :: OptType
402
oNoHeaders =
403
  (Option "" ["no-headers"]
404
   (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
405
   "do not show a header line",
406
   OptComplNone)
407

    
408
oNoSimulation :: OptType
409
oNoSimulation =
410
  (Option "" ["no-simulation"]
411
   (NoArg (\opts -> Ok opts {optNoSimulation = True}))
412
   "do not perform rebalancing simulation",
413
   OptComplNone)
414

    
415
oNodeSim :: OptType
416
oNodeSim =
417
  (Option "" ["simulate"]
418
   (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
419
   "simulate an empty cluster, given as\
420
   \ 'alloc_policy,num_nodes,disk,ram,cpu'",
421
   OptComplString)
422

    
423
oOfflineNode :: OptType
424
oOfflineNode =
425
  (Option "O" ["offline"]
426
   (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
427
   "set node as offline",
428
   OptComplOneNode)
429

    
430
oOutputDir :: OptType
431
oOutputDir =
432
  (Option "d" ["output-dir"]
433
   (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
434
   "directory in which to write output files",
435
   OptComplDir)
436

    
437
oPrintCommands :: OptType
438
oPrintCommands =
439
  (Option "C" ["print-commands"]
440
   (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
441
            fromMaybe "-")
442
    "FILE")
443
   "print the ganeti command list for reaching the solution,\
444
   \ if an argument is passed then write the commands to a\
445
   \ file named as such",
446
   OptComplNone)
447

    
448
oPrintInsts :: OptType
449
oPrintInsts =
450
  (Option "" ["print-instances"]
451
   (NoArg (\ opts -> Ok opts { optShowInsts = True }))
452
   "print the final instance map",
453
   OptComplNone)
454

    
455
oPrintNodes :: OptType
456
oPrintNodes =
457
  (Option "p" ["print-nodes"]
458
   (OptArg ((\ f opts ->
459
               let (prefix, realf) = case f of
460
                                       '+':rest -> (["+"], rest)
461
                                       _ -> ([], f)
462
                   splitted = prefix ++ sepSplit ',' realf
463
               in Ok opts { optShowNodes = Just splitted }) .
464
            fromMaybe []) "FIELDS")
465
   "print the final node list",
466
   OptComplNone)
467

    
468
oQuiet :: OptType
469
oQuiet =
470
  (Option "q" ["quiet"]
471
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
472
   "decrease the verbosity level",
473
   OptComplNone)
474

    
475
oRapiMaster :: OptType
476
oRapiMaster =
477
  (Option "m" ["master"]
478
   (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
479
   "collect data via RAPI at the given ADDRESS",
480
   OptComplHost)
481

    
482
oSaveCluster :: OptType
483
oSaveCluster =
484
  (Option "S" ["save"]
485
   (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
486
   "Save cluster state at the end of the processing to FILE",
487
   OptComplNone)
488

    
489
oStdSpec :: OptType
490
oStdSpec =
491
  (Option "" ["standard-alloc"]
492
   (ReqArg (\ inp opts -> do
493
              tspec <- parseISpecString "standard" inp
494
              return $ opts { optStdSpec = Just tspec } )
495
    "STDSPEC")
496
   "enable standard specs allocation, given as 'disk,ram,cpu'",
497
   OptComplString)
498

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

    
509
oVerbose :: OptType
510
oVerbose =
511
  (Option "v" ["verbose"]
512
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
513
   "increase the verbosity level",
514
   OptComplNone)
515

    
516
-- | Generic options.
517
genericOpts :: [GenericOptType Options]
518
genericOpts =  [ oShowVer
519
               , oShowHelp
520
               , oShowComp
521
               ]
522

    
523
-- * Functions
524

    
525
-- | Wrapper over 'Common.parseOpts' with our custom options.
526
parseOpts :: [String]               -- ^ The command line arguments
527
          -> String                 -- ^ The program name
528
          -> [OptType]              -- ^ The supported command line options
529
          -> IO (Options, [String]) -- ^ The resulting options and leftover
530
                                    -- arguments
531
parseOpts = Common.parseOpts defaultOptions
532

    
533

    
534
-- | A shell script template for autogenerated scripts.
535
shTemplate :: String
536
shTemplate =
537
  printf "#!/bin/sh\n\n\
538
         \# Auto-generated script for executing cluster rebalancing\n\n\
539
         \# To stop, touch the file /tmp/stop-htools\n\n\
540
         \set -e\n\n\
541
         \check() {\n\
542
         \  if [ -f /tmp/stop-htools ]; then\n\
543
         \    echo 'Stop requested, exiting'\n\
544
         \    exit 0\n\
545
         \  fi\n\
546
         \}\n\n"
547

    
548
-- | Optionally print the node list.
549
maybePrintNodes :: Maybe [String]       -- ^ The field list
550
                -> String               -- ^ Informational message
551
                -> ([String] -> String) -- ^ Function to generate the listing
552
                -> IO ()
553
maybePrintNodes Nothing _ _ = return ()
554
maybePrintNodes (Just fields) msg fn = do
555
  hPutStrLn stderr ""
556
  hPutStrLn stderr (msg ++ " status:")
557
  hPutStrLn stderr $ fn fields
558

    
559
-- | Optionally print the instance list.
560
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
561
                -> String -- ^ Type of the instance map (e.g. initial)
562
                -> String -- ^ The instance data
563
                -> IO ()
564
maybePrintInsts do_print msg instdata =
565
  when do_print $ do
566
    hPutStrLn stderr ""
567
    hPutStrLn stderr $ msg ++ " instance map:"
568
    hPutStr stderr instdata
569

    
570
-- | Function to display warning messages from parsing the cluster
571
-- state.
572
maybeShowWarnings :: [String] -- ^ The warning messages
573
                  -> IO ()
574
maybeShowWarnings fix_msgs =
575
  unless (null fix_msgs) $ do
576
    hPutStrLn stderr "Warning: cluster has inconsistent data:"
577
    hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
578

    
579
-- | Format a list of key, value as a shell fragment.
580
printKeys :: String              -- ^ Prefix to printed variables
581
          -> [(String, String)]  -- ^ List of (key, value) pairs to be printed
582
          -> IO ()
583
printKeys prefix =
584
  mapM_ (\(k, v) ->
585
           printf "%s_%s=%s\n" prefix (map toUpper k) (ensureQuoted v))
586

    
587
-- | Prints the final @OK@ marker in machine readable output.
588
printFinal :: String    -- ^ Prefix to printed variable
589
           -> Bool      -- ^ Whether output should be machine readable;
590
                        -- note: if not, there is nothing to print
591
           -> IO ()
592
printFinal prefix True =
593
  -- this should be the final entry
594
  printKeys prefix [("OK", "1")]
595

    
596
printFinal _ False = return ()
597

    
598
-- | Potentially set the node as offline based on passed offline list.
599
setNodeOffline :: [Ndx] -> Node.Node -> Node.Node
600
setNodeOffline offline_indices n =
601
  if Node.idx n `elem` offline_indices
602
    then Node.setOffline n True
603
    else n
604

    
605
-- | Set node properties based on command line options.
606
setNodeStatus :: Options -> Node.List -> IO Node.List
607
setNodeStatus opts fixed_nl = do
608
  let offline_passed = optOffline opts
609
      all_nodes = Container.elems fixed_nl
610
      offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
611
      offline_wrong = filter (not . goodLookupResult) offline_lkp
612
      offline_names = map lrContent offline_lkp
613
      offline_indices = map Node.idx $
614
                        filter (\n -> Node.name n `elem` offline_names)
615
                               all_nodes
616
      m_cpu = optMcpu opts
617
      m_dsk = optMdsk opts
618

    
619
  unless (null offline_wrong) .
620
         exitErr $ printf "wrong node name(s) set as offline: %s\n"
621
                   (commaJoin (map lrContent offline_wrong))
622
  let setMCpuFn = case m_cpu of
623
                    Nothing -> id
624
                    Just new_mcpu -> flip Node.setMcpu new_mcpu
625
  let nm = Container.map (setNodeOffline offline_indices .
626
                          flip Node.setMdsk m_dsk .
627
                          setMCpuFn) fixed_nl
628
  return nm