Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ b7743258

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.HTools.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
  , parseOpts
34
  , parseOptsInner
35
  , parseYesNo
36
  , parseISpecString
37
  , shTemplate
38
  , defaultLuxiSocket
39
  , maybePrintNodes
40
  , maybePrintInsts
41
  , maybeShowWarnings
42
  , setNodeStatus
43
  -- * The options
44
  , oDataFile
45
  , oDiskMoves
46
  , oDiskTemplate
47
  , oDynuFile
48
  , oEvacMode
49
  , oExInst
50
  , oExTags
51
  , oExecJobs
52
  , oGroup
53
  , oIAllocSrc
54
  , oInstMoves
55
  , oLuxiSocket
56
  , oMachineReadable
57
  , oMaxCpu
58
  , oMaxSolLength
59
  , oMinDisk
60
  , oMinGain
61
  , oMinGainLim
62
  , oMinScore
63
  , oNoHeaders
64
  , oNodeSim
65
  , oOfflineNode
66
  , oOutputDir
67
  , oPrintCommands
68
  , oPrintInsts
69
  , oPrintNodes
70
  , oQuiet
71
  , oRapiMaster
72
  , oReplay
73
  , oSaveCluster
74
  , oSelInst
75
  , oShowHelp
76
  , oShowVer
77
  , oStdSpec
78
  , oTestCount
79
  , oTieredSpec
80
  , oVerbose
81
  ) where
82

    
83
import Control.Monad
84
import Data.Maybe (fromMaybe)
85
import qualified Data.Version
86
import System.Console.GetOpt
87
import System.IO
88
import System.Info
89
import System.Exit
90
import Text.Printf (printf, hPrintf)
91

    
92
import qualified Ganeti.HTools.Version as Version(version)
93
import qualified Ganeti.HTools.Container as Container
94
import qualified Ganeti.HTools.Node as Node
95
import qualified Ganeti.Constants as C
96
import Ganeti.HTools.Types
97
import Ganeti.HTools.Utils
98
import Ganeti.HTools.Loader
99

    
100
-- * Constants
101

    
102
-- | The default value for the luxi socket.
103
--
104
-- This is re-exported from the "Ganeti.Constants" module.
105
defaultLuxiSocket :: FilePath
106
defaultLuxiSocket = C.masterSocket
107

    
108
-- * Data types
109

    
110
-- | Command line options structure.
111
data Options = Options
112
  { optDataFile    :: Maybe FilePath -- ^ Path to the cluster data file
113
  , optDiskMoves   :: Bool           -- ^ Allow disk moves
114
  , optInstMoves   :: Bool           -- ^ Allow instance moves
115
  , optDiskTemplate :: Maybe DiskTemplate  -- ^ Override for the disk template
116
  , optDynuFile    :: Maybe FilePath -- ^ Optional file with dynamic use data
117
  , optEvacMode    :: Bool           -- ^ Enable evacuation mode
118
  , optExInst      :: [String]       -- ^ Instances to be excluded
119
  , optExTags      :: Maybe [String] -- ^ Tags to use for exclusion
120
  , optExecJobs    :: Bool           -- ^ Execute the commands via Luxi
121
  , optGroup       :: Maybe GroupID  -- ^ The UUID of the group to process
122
  , optIAllocSrc   :: Maybe FilePath -- ^ The iallocation spec
123
  , optSelInst     :: [String]       -- ^ Instances to be excluded
124
  , optLuxi        :: Maybe FilePath -- ^ Collect data from Luxi
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
  , optNodeSim     :: [String]       -- ^ Cluster simulation mode
135
  , optOffline     :: [String]       -- ^ Names of offline nodes
136
  , optOutPath     :: FilePath       -- ^ Path to the output directory
137
  , optSaveCluster :: Maybe FilePath -- ^ Save cluster state to this file
138
  , optShowCmds    :: Maybe FilePath -- ^ Whether to show the command list
139
  , optShowHelp    :: Bool           -- ^ Just show the help
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
  , optDynuFile    = Nothing
158
  , optEvacMode    = False
159
  , optExInst      = []
160
  , optExTags      = Nothing
161
  , optExecJobs    = False
162
  , optGroup       = Nothing
163
  , optIAllocSrc   = Nothing
164
  , optSelInst     = []
165
  , optLuxi        = Nothing
166
  , optMachineReadable = False
167
  , optMaster      = ""
168
  , optMaxLength   = -1
169
  , optMcpu        = Nothing
170
  , optMdsk        = defReservedDiskRatio
171
  , optMinGain     = 1e-2
172
  , optMinGainLim  = 1e-1
173
  , optMinScore    = 1e-9
174
  , optNoHeaders   = False
175
  , optNodeSim     = []
176
  , optOffline     = []
177
  , optOutPath     = "."
178
  , optSaveCluster = Nothing
179
  , optShowCmds    = Nothing
180
  , optShowHelp    = 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 = OptDescr (Options -> Result Options)
193

    
194
-- * Helper functions
195

    
196
parseISpecString :: String -> String -> Result RSpec
197
parseISpecString descr inp = do
198
  let sp = sepSplit ',' inp
199
      err = Bad ("Invalid " ++ descr ++ " specification: '" ++ inp ++
200
                 "', expected disk,ram,cpu")
201
  when (length sp /= 3) err
202
  prs <- mapM (\(fn, val) -> fn val) $
203
         zip [ annotateResult (descr ++ " specs disk") . parseUnit
204
             , annotateResult (descr ++ " specs memory") . parseUnit
205
             , tryRead (descr ++ " specs cpus")
206
             ] sp
207
  case prs of
208
    [dsk, ram, cpu] -> return $ RSpec cpu ram dsk
209
    _ -> err
210

    
211
-- * Command line options
212

    
213
oDataFile :: OptType
214
oDataFile = Option "t" ["text-data"]
215
            (ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
216
            "the cluster data FILE"
217

    
218
oDiskMoves :: OptType
219
oDiskMoves = Option "" ["no-disk-moves"]
220
             (NoArg (\ opts -> Ok opts { optDiskMoves = False}))
221
             "disallow disk moves from the list of allowed instance changes,\
222
             \ thus allowing only the 'cheap' failover/migrate operations"
223

    
224
oDiskTemplate :: OptType
225
oDiskTemplate = Option "" ["disk-template"]
226
                (ReqArg (\ t opts -> do
227
                           dt <- diskTemplateFromRaw t
228
                           return $ opts { optDiskTemplate = Just dt })
229
                 "TEMPLATE") "select the desired disk template"
230

    
231
oSelInst :: OptType
232
oSelInst = Option "" ["select-instances"]
233
          (ReqArg (\ f opts -> Ok opts { optSelInst = sepSplit ',' f }) "INSTS")
234
          "only select given instances for any moves"
235

    
236
oInstMoves :: OptType
237
oInstMoves = Option "" ["no-instance-moves"]
238
             (NoArg (\ opts -> Ok opts { optInstMoves = False}))
239
             "disallow instance (primary node) moves from the list of allowed,\
240
             \ instance changes, thus allowing only slower, but sometimes\
241
             \ safer, drbd secondary changes"
242

    
243
oDynuFile :: OptType
244
oDynuFile = Option "U" ["dynu-file"]
245
            (ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
246
            "Import dynamic utilisation data from the given FILE"
247

    
248
oEvacMode :: OptType
249
oEvacMode = Option "E" ["evac-mode"]
250
            (NoArg (\opts -> Ok opts { optEvacMode = True }))
251
            "enable evacuation mode, where the algorithm only moves \
252
            \ instances away from offline and drained nodes"
253

    
254
oExInst :: OptType
255
oExInst = Option "" ["exclude-instances"]
256
          (ReqArg (\ f opts -> Ok opts { optExInst = sepSplit ',' f }) "INSTS")
257
          "exclude given instances from any moves"
258

    
259
oExTags :: OptType
260
oExTags = Option "" ["exclusion-tags"]
261
            (ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
262
             "TAG,...") "Enable instance exclusion based on given tag prefix"
263

    
264
oExecJobs :: OptType
265
oExecJobs = Option "X" ["exec"]
266
             (NoArg (\ opts -> Ok opts { optExecJobs = True}))
267
             "execute the suggested moves via Luxi (only available when using\
268
             \ it for data gathering)"
269

    
270
oGroup :: OptType
271
oGroup = Option "G" ["group"]
272
            (ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
273
            "the ID of the group to balance"
274

    
275
oIAllocSrc :: OptType
276
oIAllocSrc = Option "I" ["ialloc-src"]
277
             (ReqArg (\ f opts -> Ok opts { optIAllocSrc = Just f }) "FILE")
278
             "Specify an iallocator spec as the cluster data source"
279

    
280
oLuxiSocket :: OptType
281
oLuxiSocket = Option "L" ["luxi"]
282
              (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
283
                       fromMaybe defaultLuxiSocket) "SOCKET")
284
              "collect data via Luxi, optionally using the given SOCKET path"
285

    
286
oMachineReadable :: OptType
287
oMachineReadable = Option "" ["machine-readable"]
288
                   (OptArg (\ f opts -> do
289
                     flag <- parseYesNo True f
290
                     return $ opts { optMachineReadable = flag }) "CHOICE")
291
          "enable machine readable output (pass either 'yes' or 'no' to\
292
          \ explicitely control the flag, or without an argument defaults to\
293
          \ yes"
294

    
295
oMaxCpu :: OptType
296
oMaxCpu = Option "" ["max-cpu"]
297
          (ReqArg (\ n opts -> do
298
                     mcpu <- tryRead "parsing max-cpu" n
299
                     when (mcpu <= 0) $
300
                          fail "Invalid value of the max-cpu ratio,\
301
                               \ expected >0"
302
                     return $ opts { optMcpu = Just mcpu }) "RATIO")
303
          "maximum virtual-to-physical cpu ratio for nodes (from 0\
304
          \ upwards) [default read from cluster]"
305

    
306
oMaxSolLength :: OptType
307
oMaxSolLength = Option "l" ["max-length"]
308
                (ReqArg (\ i opts -> Ok opts { optMaxLength = read i }) "N")
309
                "cap the solution at this many balancing or allocation \
310
                \ rounds (useful for very unbalanced clusters or empty \
311
                \ clusters)"
312

    
313
oMinDisk :: OptType
314
oMinDisk = Option "" ["min-disk"]
315
           (ReqArg (\ n opts -> Ok opts { optMdsk = read n }) "RATIO")
316
           "minimum free disk space for nodes (between 0 and 1) [0]"
317

    
318
oMinGain :: OptType
319
oMinGain = Option "g" ["min-gain"]
320
            (ReqArg (\ g opts -> Ok opts { optMinGain = read g }) "DELTA")
321
            "minimum gain to aim for in a balancing step before giving up"
322

    
323
oMinGainLim :: OptType
324
oMinGainLim = Option "" ["min-gain-limit"]
325
            (ReqArg (\ g opts -> Ok opts { optMinGainLim = read g }) "SCORE")
326
            "minimum cluster score for which we start checking the min-gain"
327

    
328
oMinScore :: OptType
329
oMinScore = Option "e" ["min-score"]
330
            (ReqArg (\ e opts -> Ok opts { optMinScore = read e }) "EPSILON")
331
            "mininum score to aim for"
332

    
333
oNoHeaders :: OptType
334
oNoHeaders = Option "" ["no-headers"]
335
             (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
336
             "do not show a header line"
337

    
338
oNodeSim :: OptType
339
oNodeSim = Option "" ["simulate"]
340
            (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
341
            "simulate an empty cluster, given as 'num_nodes,disk,ram,cpu'"
342

    
343
oOfflineNode :: OptType
344
oOfflineNode = Option "O" ["offline"]
345
               (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
346
               "set node as offline"
347

    
348
oOutputDir :: OptType
349
oOutputDir = Option "d" ["output-dir"]
350
             (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
351
             "directory in which to write output files"
352

    
353
oPrintCommands :: OptType
354
oPrintCommands = Option "C" ["print-commands"]
355
                 (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
356
                          fromMaybe "-")
357
                  "FILE")
358
                 "print the ganeti command list for reaching the solution,\
359
                 \ if an argument is passed then write the commands to a\
360
                 \ file named as such"
361

    
362
oPrintInsts :: OptType
363
oPrintInsts = Option "" ["print-instances"]
364
              (NoArg (\ opts -> Ok opts { optShowInsts = True }))
365
              "print the final instance map"
366

    
367
oPrintNodes :: OptType
368
oPrintNodes = Option "p" ["print-nodes"]
369
              (OptArg ((\ f opts ->
370
                          let (prefix, realf) = case f of
371
                                                  '+':rest -> (["+"], rest)
372
                                                  _ -> ([], f)
373
                              splitted = prefix ++ sepSplit ',' realf
374
                          in Ok opts { optShowNodes = Just splitted }) .
375
                       fromMaybe []) "FIELDS")
376
              "print the final node list"
377

    
378
oQuiet :: OptType
379
oQuiet = Option "q" ["quiet"]
380
         (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
381
         "decrease the verbosity level"
382

    
383
oRapiMaster :: OptType
384
oRapiMaster = Option "m" ["master"]
385
              (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
386
              "collect data via RAPI at the given ADDRESS"
387

    
388
oSaveCluster :: OptType
389
oSaveCluster = Option "S" ["save"]
390
            (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
391
            "Save cluster state at the end of the processing to FILE"
392

    
393
oShowHelp :: OptType
394
oShowHelp = Option "h" ["help"]
395
            (NoArg (\ opts -> Ok opts { optShowHelp = True}))
396
            "show help"
397

    
398
oShowVer :: OptType
399
oShowVer = Option "V" ["version"]
400
           (NoArg (\ opts -> Ok opts { optShowVer = True}))
401
           "show the version of the program"
402

    
403
oStdSpec :: OptType
404
oStdSpec = Option "" ["standard-alloc"]
405
             (ReqArg (\ inp opts -> do
406
                        tspec <- parseISpecString "standard" inp
407
                        return $ opts { optStdSpec = Just tspec } )
408
              "STDSPEC")
409
             "enable standard specs allocation, given as 'disk,ram,cpu'"
410

    
411
oTestCount :: OptType
412
oTestCount = Option "" ["test-count"]
413
             (ReqArg (\ inp opts -> do
414
                        tcount <- tryRead "parsing test count" inp
415
                        return $ opts { optTestCount = Just tcount } )
416
              "COUNT")
417
             "override the target test count"
418

    
419
oTieredSpec :: OptType
420
oTieredSpec = Option "" ["tiered-alloc"]
421
             (ReqArg (\ inp opts -> do
422
                        tspec <- parseISpecString "tiered" inp
423
                        return $ opts { optTieredSpec = Just tspec } )
424
              "TSPEC")
425
             "enable tiered specs allocation, given as 'disk,ram,cpu'"
426

    
427
oReplay :: OptType
428
oReplay = Option "" ["replay"]
429
          (ReqArg (\ stat opts -> Ok opts { optReplay = Just stat } ) "STATE")
430
          "Pre-seed the random number generator with STATE"
431

    
432
oVerbose :: OptType
433
oVerbose = Option "v" ["verbose"]
434
           (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
435
           "increase the verbosity level"
436

    
437
-- * Functions
438

    
439
-- | Helper for parsing a yes\/no command line flag.
440
parseYesNo :: Bool         -- ^ Default value (when we get a @Nothing@)
441
           -> Maybe String -- ^ Parameter value
442
           -> Result Bool  -- ^ Resulting boolean value
443
parseYesNo v Nothing      = return v
444
parseYesNo _ (Just "yes") = return True
445
parseYesNo _ (Just "no")  = return False
446
parseYesNo _ (Just s)     = fail ("Invalid choice '" ++ s ++
447
                                  "', pass one of 'yes' or 'no'")
448

    
449
-- | Usage info.
450
usageHelp :: String -> [OptType] -> String
451
usageHelp progname =
452
  usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
453
             progname Version.version progname)
454

    
455
-- | Show the program version info.
456
versionInfo :: String -> String
457
versionInfo progname =
458
  printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
459
         progname Version.version compilerName
460
         (Data.Version.showVersion compilerVersion)
461
         os arch
462

    
463
-- | Command line parser, using the 'Options' structure.
464
parseOpts :: [String]               -- ^ The command line arguments
465
          -> String                 -- ^ The program name
466
          -> [OptType]              -- ^ The supported command line options
467
          -> IO (Options, [String]) -- ^ The resulting options and leftover
468
                                    -- arguments
469
parseOpts argv progname options =
470
  case parseOptsInner argv progname options of
471
    Left (code, msg) -> do
472
      hPutStr (if code == 0 then stdout else stderr) msg
473
      exitWith (if code == 0 then ExitSuccess else ExitFailure code)
474
    Right result ->
475
      return result
476

    
477
-- | Inner parse options. The arguments are similar to 'parseOpts',
478
-- but it returns either a 'Left' composed of exit code and message,
479
-- or a 'Right' for the success case.
480
parseOptsInner :: [String] -> String -> [OptType]
481
               -> Either (Int, String) (Options, [String])
482
parseOptsInner argv progname options =
483
  case getOpt Permute options argv of
484
    (o, n, []) ->
485
      let (pr, args) = (foldM (flip id) defaultOptions o, n)
486
      in case pr of
487
           Bad msg -> Left (1, "Error while parsing command\
488
                               \line arguments:\n" ++ msg ++ "\n")
489
           Ok po ->
490
             select (Right (po, args))
491
                 [ (optShowHelp po, Left (0, usageHelp progname options))
492
                 , (optShowVer po,  Left (0, versionInfo progname))
493
                 ]
494
    (_, _, errs) ->
495
      Left (2, "Command line error: "  ++ concat errs ++ "\n" ++
496
            usageHelp progname options)
497

    
498
-- | A shell script template for autogenerated scripts.
499
shTemplate :: String
500
shTemplate =
501
  printf "#!/bin/sh\n\n\
502
         \# Auto-generated script for executing cluster rebalancing\n\n\
503
         \# To stop, touch the file /tmp/stop-htools\n\n\
504
         \set -e\n\n\
505
         \check() {\n\
506
         \  if [ -f /tmp/stop-htools ]; then\n\
507
         \    echo 'Stop requested, exiting'\n\
508
         \    exit 0\n\
509
         \  fi\n\
510
         \}\n\n"
511

    
512
-- | Optionally print the node list.
513
maybePrintNodes :: Maybe [String]       -- ^ The field list
514
                -> String               -- ^ Informational message
515
                -> ([String] -> String) -- ^ Function to generate the listing
516
                -> IO ()
517
maybePrintNodes Nothing _ _ = return ()
518
maybePrintNodes (Just fields) msg fn = do
519
  hPutStrLn stderr ""
520
  hPutStrLn stderr (msg ++ " status:")
521
  hPutStrLn stderr $ fn fields
522

    
523

    
524
-- | Optionally print the instance list.
525
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
526
                -> String -- ^ Type of the instance map (e.g. initial)
527
                -> String -- ^ The instance data
528
                -> IO ()
529
maybePrintInsts do_print msg instdata =
530
  when do_print $ do
531
    hPutStrLn stderr ""
532
    hPutStrLn stderr $ msg ++ " instance map:"
533
    hPutStr stderr instdata
534

    
535
-- | Function to display warning messages from parsing the cluster
536
-- state.
537
maybeShowWarnings :: [String] -- ^ The warning messages
538
                  -> IO ()
539
maybeShowWarnings fix_msgs =
540
  unless (null fix_msgs) $ do
541
    hPutStrLn stderr "Warning: cluster has inconsistent data:"
542
    hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
543

    
544
-- | Potentially set the node as offline based on passed offline list.
545
setNodeOffline :: [Ndx] -> Node.Node -> Node.Node
546
setNodeOffline offline_indices n =
547
  if Node.idx n `elem` offline_indices
548
    then Node.setOffline n True
549
    else n
550

    
551
-- | Set node properties based on command line options.
552
setNodeStatus :: Options -> Node.List -> IO Node.List
553
setNodeStatus opts fixed_nl = do
554
  let offline_passed = optOffline opts
555
      all_nodes = Container.elems fixed_nl
556
      offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
557
      offline_wrong = filter (not . goodLookupResult) offline_lkp
558
      offline_names = map lrContent offline_lkp
559
      offline_indices = map Node.idx $
560
                        filter (\n -> Node.name n `elem` offline_names)
561
                               all_nodes
562
      m_cpu = optMcpu opts
563
      m_dsk = optMdsk opts
564

    
565
  unless (null offline_wrong) $ do
566
         hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
567
                     (commaJoin (map lrContent offline_wrong)) :: IO ()
568
         exitWith $ ExitFailure 1
569
  let setMCpuFn = case m_cpu of
570
                    Nothing -> id
571
                    Just new_mcpu -> flip Node.setMcpu new_mcpu
572
  let nm = Container.map (setNodeOffline offline_indices .
573
                          flip Node.setMdsk m_dsk .
574
                          setMCpuFn) fixed_nl
575
  return nm