Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (21.3 kB)

1 209b3711 Iustin Pop
{-| Implementation of command-line functions.
2 209b3711 Iustin Pop
3 525bfb36 Iustin Pop
This module holds the common command-line related functions for the
4 26d62e4c Iustin Pop
binaries, separated into this module since "Ganeti.Utils" is
5 525bfb36 Iustin Pop
used in many other places and this is more IO oriented.
6 209b3711 Iustin Pop
7 209b3711 Iustin Pop
-}
8 209b3711 Iustin Pop
9 e2fa2baf Iustin Pop
{-
10 e2fa2baf Iustin Pop
11 e247747c Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
12 e2fa2baf Iustin Pop
13 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
14 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
15 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
16 e2fa2baf Iustin Pop
(at your option) any later version.
17 e2fa2baf Iustin Pop
18 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
19 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
20 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
21 e2fa2baf Iustin Pop
General Public License for more details.
22 e2fa2baf Iustin Pop
23 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
24 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
25 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
26 e2fa2baf Iustin Pop
02110-1301, USA.
27 e2fa2baf Iustin Pop
28 e2fa2baf Iustin Pop
-}
29 e2fa2baf Iustin Pop
30 209b3711 Iustin Pop
module Ganeti.HTools.CLI
31 cd08cfa4 Iustin Pop
  ( Options(..)
32 cd08cfa4 Iustin Pop
  , OptType
33 51000365 Iustin Pop
  , defaultOptions
34 51000365 Iustin Pop
  , Ganeti.HTools.CLI.parseOpts
35 51c3d88f Iustin Pop
  , parseOptsInner
36 a7ea861a Iustin Pop
  , parseYesNo
37 8b5a517a Iustin Pop
  , parseISpecString
38 cd08cfa4 Iustin Pop
  , shTemplate
39 cd08cfa4 Iustin Pop
  , maybePrintNodes
40 cd08cfa4 Iustin Pop
  , maybePrintInsts
41 cd08cfa4 Iustin Pop
  , maybeShowWarnings
42 79eef90b Agata Murawska
  , printKeys
43 79eef90b Agata Murawska
  , printFinal
44 cd08cfa4 Iustin Pop
  , setNodeStatus
45 cd08cfa4 Iustin Pop
  -- * The options
46 cd08cfa4 Iustin Pop
  , oDataFile
47 cd08cfa4 Iustin Pop
  , oDiskMoves
48 cd08cfa4 Iustin Pop
  , oDiskTemplate
49 f0753837 René Nussbaumer
  , oSpindleUse
50 cd08cfa4 Iustin Pop
  , oDynuFile
51 cd08cfa4 Iustin Pop
  , oEvacMode
52 cd08cfa4 Iustin Pop
  , oExInst
53 cd08cfa4 Iustin Pop
  , oExTags
54 cd08cfa4 Iustin Pop
  , oExecJobs
55 7dbe4c72 Klaus Aehlig
  , oForce
56 cd08cfa4 Iustin Pop
  , oGroup
57 9899796b René Nussbaumer
  , oIAllocSrc
58 cd08cfa4 Iustin Pop
  , oInstMoves
59 8af72964 Dato Simó
  , oJobDelay
60 29a30533 Iustin Pop
  , genOLuxiSocket
61 cd08cfa4 Iustin Pop
  , oLuxiSocket
62 cd08cfa4 Iustin Pop
  , oMachineReadable
63 cd08cfa4 Iustin Pop
  , oMaxCpu
64 cd08cfa4 Iustin Pop
  , oMaxSolLength
65 cd08cfa4 Iustin Pop
  , oMinDisk
66 cd08cfa4 Iustin Pop
  , oMinGain
67 cd08cfa4 Iustin Pop
  , oMinGainLim
68 cd08cfa4 Iustin Pop
  , oMinScore
69 cd08cfa4 Iustin Pop
  , oNoHeaders
70 22e513e7 Agata Murawska
  , oNoSimulation
71 cd08cfa4 Iustin Pop
  , oNodeSim
72 cd08cfa4 Iustin Pop
  , oOfflineNode
73 cd08cfa4 Iustin Pop
  , oOutputDir
74 cd08cfa4 Iustin Pop
  , oPrintCommands
75 cd08cfa4 Iustin Pop
  , oPrintInsts
76 cd08cfa4 Iustin Pop
  , oPrintNodes
77 cd08cfa4 Iustin Pop
  , oQuiet
78 cd08cfa4 Iustin Pop
  , oRapiMaster
79 cd08cfa4 Iustin Pop
  , oSaveCluster
80 cd08cfa4 Iustin Pop
  , oSelInst
81 cd08cfa4 Iustin Pop
  , oShowHelp
82 cd08cfa4 Iustin Pop
  , oShowVer
83 097ad7ee Iustin Pop
  , oShowComp
84 294bb337 Iustin Pop
  , oStdSpec
85 cd08cfa4 Iustin Pop
  , oTieredSpec
86 cd08cfa4 Iustin Pop
  , oVerbose
87 e247747c Iustin Pop
  , oPriority
88 42834645 Iustin Pop
  , genericOpts
89 cd08cfa4 Iustin Pop
  ) where
90 209b3711 Iustin Pop
91 cc532bdd Iustin Pop
import Control.Monad
92 79eef90b Agata Murawska
import Data.Char (toUpper)
93 e8f89bb6 Iustin Pop
import Data.Maybe (fromMaybe)
94 209b3711 Iustin Pop
import System.Console.GetOpt
95 209b3711 Iustin Pop
import System.IO
96 88a10df5 Iustin Pop
import Text.Printf (printf)
97 209b3711 Iustin Pop
98 5296ee23 Iustin Pop
import qualified Ganeti.HTools.Container as Container
99 5296ee23 Iustin Pop
import qualified Ganeti.HTools.Node as Node
100 9eeb0aa5 Michael Hanselmann
import qualified Ganeti.Path as Path
101 92e32d76 Iustin Pop
import Ganeti.HTools.Types
102 2fc5653f Iustin Pop
import Ganeti.BasicTypes
103 51000365 Iustin Pop
import Ganeti.Common as Common
104 e247747c Iustin Pop
import Ganeti.Types
105 26d62e4c Iustin Pop
import Ganeti.Utils
106 fae371cc Iustin Pop
107 525bfb36 Iustin Pop
-- * Data types
108 525bfb36 Iustin Pop
109 0427285d Iustin Pop
-- | Command line options structure.
110 0427285d Iustin Pop
data Options = Options
111 cd08cfa4 Iustin Pop
  { optDataFile    :: Maybe FilePath -- ^ Path to the cluster data file
112 cd08cfa4 Iustin Pop
  , optDiskMoves   :: Bool           -- ^ Allow disk moves
113 cd08cfa4 Iustin Pop
  , optInstMoves   :: Bool           -- ^ Allow instance moves
114 9fdd3d0f Iustin Pop
  , optDiskTemplate :: Maybe DiskTemplate  -- ^ Override for the disk template
115 f0753837 René Nussbaumer
  , optSpindleUse  :: Maybe Int      -- ^ Override for the spindle usage
116 cd08cfa4 Iustin Pop
  , optDynuFile    :: Maybe FilePath -- ^ Optional file with dynamic use data
117 cd08cfa4 Iustin Pop
  , optEvacMode    :: Bool           -- ^ Enable evacuation mode
118 cd08cfa4 Iustin Pop
  , optExInst      :: [String]       -- ^ Instances to be excluded
119 cd08cfa4 Iustin Pop
  , optExTags      :: Maybe [String] -- ^ Tags to use for exclusion
120 cd08cfa4 Iustin Pop
  , optExecJobs    :: Bool           -- ^ Execute the commands via Luxi
121 7dbe4c72 Klaus Aehlig
  , optForce       :: Bool           -- ^ Force the execution
122 cd08cfa4 Iustin Pop
  , optGroup       :: Maybe GroupID  -- ^ The UUID of the group to process
123 9899796b René Nussbaumer
  , optIAllocSrc   :: Maybe FilePath -- ^ The iallocation spec
124 cd08cfa4 Iustin Pop
  , optSelInst     :: [String]       -- ^ Instances to be excluded
125 cd08cfa4 Iustin Pop
  , optLuxi        :: Maybe FilePath -- ^ Collect data from Luxi
126 8af72964 Dato Simó
  , optJobDelay    :: Double         -- ^ Delay before executing first job
127 cd08cfa4 Iustin Pop
  , optMachineReadable :: Bool       -- ^ Output machine-readable format
128 cd08cfa4 Iustin Pop
  , optMaster      :: String         -- ^ Collect data from RAPI
129 cd08cfa4 Iustin Pop
  , optMaxLength   :: Int            -- ^ Stop after this many steps
130 284e9822 Iustin Pop
  , optMcpu        :: Maybe Double   -- ^ Override max cpu ratio for nodes
131 cd08cfa4 Iustin Pop
  , optMdsk        :: Double         -- ^ Max disk usage ratio for nodes
132 cd08cfa4 Iustin Pop
  , optMinGain     :: Score          -- ^ Min gain we aim for in a step
133 cd08cfa4 Iustin Pop
  , optMinGainLim  :: Score          -- ^ Limit below which we apply mingain
134 cd08cfa4 Iustin Pop
  , optMinScore    :: Score          -- ^ The minimum score we aim for
135 cd08cfa4 Iustin Pop
  , optNoHeaders   :: Bool           -- ^ Do not show a header line
136 22e513e7 Agata Murawska
  , optNoSimulation :: Bool          -- ^ Skip the rebalancing dry-run
137 cd08cfa4 Iustin Pop
  , optNodeSim     :: [String]       -- ^ Cluster simulation mode
138 cd08cfa4 Iustin Pop
  , optOffline     :: [String]       -- ^ Names of offline nodes
139 cd08cfa4 Iustin Pop
  , optOutPath     :: FilePath       -- ^ Path to the output directory
140 cd08cfa4 Iustin Pop
  , optSaveCluster :: Maybe FilePath -- ^ Save cluster state to this file
141 cd08cfa4 Iustin Pop
  , optShowCmds    :: Maybe FilePath -- ^ Whether to show the command list
142 cd08cfa4 Iustin Pop
  , optShowHelp    :: Bool           -- ^ Just show the help
143 097ad7ee Iustin Pop
  , optShowComp    :: Bool           -- ^ Just show the completion info
144 cd08cfa4 Iustin Pop
  , optShowInsts   :: Bool           -- ^ Whether to show the instance map
145 cd08cfa4 Iustin Pop
  , optShowNodes   :: Maybe [String] -- ^ Whether to show node status
146 cd08cfa4 Iustin Pop
  , optShowVer     :: Bool           -- ^ Just show the program version
147 be468da0 Iustin Pop
  , optStdSpec     :: Maybe RSpec    -- ^ Requested standard specs
148 ee4ffc8a Iustin Pop
  , optTestCount   :: Maybe Int      -- ^ Optional test count override
149 cd08cfa4 Iustin Pop
  , optTieredSpec  :: Maybe RSpec    -- ^ Requested specs for tiered mode
150 cd08cfa4 Iustin Pop
  , optReplay      :: Maybe String   -- ^ Unittests: RNG state
151 cd08cfa4 Iustin Pop
  , optVerbose     :: Int            -- ^ Verbosity level
152 e247747c Iustin Pop
  , optPriority    :: Maybe OpSubmitPriority -- ^ OpCode submit priority
153 cd08cfa4 Iustin Pop
  } deriving Show
154 0427285d Iustin Pop
155 0427285d Iustin Pop
-- | Default values for the command line options.
156 0427285d Iustin Pop
defaultOptions :: Options
157 0427285d Iustin Pop
defaultOptions  = Options
158 cd08cfa4 Iustin Pop
  { optDataFile    = Nothing
159 cd08cfa4 Iustin Pop
  , optDiskMoves   = True
160 cd08cfa4 Iustin Pop
  , optInstMoves   = True
161 9fdd3d0f Iustin Pop
  , optDiskTemplate = Nothing
162 f0753837 René Nussbaumer
  , optSpindleUse  = Nothing
163 cd08cfa4 Iustin Pop
  , optDynuFile    = Nothing
164 cd08cfa4 Iustin Pop
  , optEvacMode    = False
165 cd08cfa4 Iustin Pop
  , optExInst      = []
166 cd08cfa4 Iustin Pop
  , optExTags      = Nothing
167 cd08cfa4 Iustin Pop
  , optExecJobs    = False
168 7dbe4c72 Klaus Aehlig
  , optForce       = False
169 cd08cfa4 Iustin Pop
  , optGroup       = Nothing
170 9899796b René Nussbaumer
  , optIAllocSrc   = Nothing
171 cd08cfa4 Iustin Pop
  , optSelInst     = []
172 cd08cfa4 Iustin Pop
  , optLuxi        = Nothing
173 8af72964 Dato Simó
  , optJobDelay    = 10
174 cd08cfa4 Iustin Pop
  , optMachineReadable = False
175 cd08cfa4 Iustin Pop
  , optMaster      = ""
176 cd08cfa4 Iustin Pop
  , optMaxLength   = -1
177 284e9822 Iustin Pop
  , optMcpu        = Nothing
178 cd08cfa4 Iustin Pop
  , optMdsk        = defReservedDiskRatio
179 cd08cfa4 Iustin Pop
  , optMinGain     = 1e-2
180 cd08cfa4 Iustin Pop
  , optMinGainLim  = 1e-1
181 cd08cfa4 Iustin Pop
  , optMinScore    = 1e-9
182 cd08cfa4 Iustin Pop
  , optNoHeaders   = False
183 22e513e7 Agata Murawska
  , optNoSimulation = False
184 cd08cfa4 Iustin Pop
  , optNodeSim     = []
185 cd08cfa4 Iustin Pop
  , optOffline     = []
186 cd08cfa4 Iustin Pop
  , optOutPath     = "."
187 cd08cfa4 Iustin Pop
  , optSaveCluster = Nothing
188 cd08cfa4 Iustin Pop
  , optShowCmds    = Nothing
189 cd08cfa4 Iustin Pop
  , optShowHelp    = False
190 097ad7ee Iustin Pop
  , optShowComp    = False
191 cd08cfa4 Iustin Pop
  , optShowInsts   = False
192 cd08cfa4 Iustin Pop
  , optShowNodes   = Nothing
193 cd08cfa4 Iustin Pop
  , optShowVer     = False
194 be468da0 Iustin Pop
  , optStdSpec     = Nothing
195 ee4ffc8a Iustin Pop
  , optTestCount   = Nothing
196 cd08cfa4 Iustin Pop
  , optTieredSpec  = Nothing
197 cd08cfa4 Iustin Pop
  , optReplay      = Nothing
198 cd08cfa4 Iustin Pop
  , optVerbose     = 1
199 e247747c Iustin Pop
  , optPriority    = Nothing
200 cd08cfa4 Iustin Pop
  }
201 0427285d Iustin Pop
202 55abd2c7 Iustin Pop
-- | Abbreviation for the option type.
203 51000365 Iustin Pop
type OptType = GenericOptType Options
204 51000365 Iustin Pop
205 51000365 Iustin Pop
instance StandardOptions Options where
206 51000365 Iustin Pop
  helpRequested = optShowHelp
207 51000365 Iustin Pop
  verRequested  = optShowVer
208 097ad7ee Iustin Pop
  compRequested = optShowComp
209 5b11f8db Iustin Pop
  requestHelp o = o { optShowHelp = True }
210 5b11f8db Iustin Pop
  requestVer  o = o { optShowVer  = True }
211 097ad7ee Iustin Pop
  requestComp o = o { optShowComp = True }
212 0427285d Iustin Pop
213 7da760ca Iustin Pop
-- * Helper functions
214 7da760ca Iustin Pop
215 7da760ca Iustin Pop
parseISpecString :: String -> String -> Result RSpec
216 7da760ca Iustin Pop
parseISpecString descr inp = do
217 7da760ca Iustin Pop
  let sp = sepSplit ',' inp
218 8b5a517a Iustin Pop
      err = Bad ("Invalid " ++ descr ++ " specification: '" ++ inp ++
219 8b5a517a Iustin Pop
                 "', expected disk,ram,cpu")
220 8b5a517a Iustin Pop
  when (length sp /= 3) err
221 7da760ca Iustin Pop
  prs <- mapM (\(fn, val) -> fn val) $
222 8b5a517a Iustin Pop
         zip [ annotateResult (descr ++ " specs disk") . parseUnit
223 8b5a517a Iustin Pop
             , annotateResult (descr ++ " specs memory") . parseUnit
224 7da760ca Iustin Pop
             , tryRead (descr ++ " specs cpus")
225 7da760ca Iustin Pop
             ] sp
226 7da760ca Iustin Pop
  case prs of
227 7da760ca Iustin Pop
    [dsk, ram, cpu] -> return $ RSpec cpu ram dsk
228 8b5a517a Iustin Pop
    _ -> err
229 7da760ca Iustin Pop
230 ce207617 Iustin Pop
-- | Disk template choices.
231 ce207617 Iustin Pop
optComplDiskTemplate :: OptCompletion
232 ce207617 Iustin Pop
optComplDiskTemplate = OptComplChoices $
233 ce207617 Iustin Pop
                       map diskTemplateToRaw [minBound..maxBound]
234 ce207617 Iustin Pop
235 525bfb36 Iustin Pop
-- * Command line options
236 525bfb36 Iustin Pop
237 16c2369c Iustin Pop
oDataFile :: OptType
238 ce207617 Iustin Pop
oDataFile =
239 ce207617 Iustin Pop
  (Option "t" ["text-data"]
240 ce207617 Iustin Pop
   (ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
241 ce207617 Iustin Pop
   "the cluster data FILE",
242 ce207617 Iustin Pop
   OptComplFile)
243 0427285d Iustin Pop
244 df18fdfe Iustin Pop
oDiskMoves :: OptType
245 ce207617 Iustin Pop
oDiskMoves =
246 ce207617 Iustin Pop
  (Option "" ["no-disk-moves"]
247 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optDiskMoves = False}))
248 ce207617 Iustin Pop
   "disallow disk moves from the list of allowed instance changes,\
249 ce207617 Iustin Pop
   \ thus allowing only the 'cheap' failover/migrate operations",
250 ce207617 Iustin Pop
   OptComplNone)
251 b2278348 Iustin Pop
252 c4bb977b Iustin Pop
oDiskTemplate :: OptType
253 ce207617 Iustin Pop
oDiskTemplate =
254 ce207617 Iustin Pop
  (Option "" ["disk-template"]
255 ce207617 Iustin Pop
   (reqWithConversion diskTemplateFromRaw
256 ce207617 Iustin Pop
    (\dt opts -> Ok opts { optDiskTemplate = Just dt })
257 ce207617 Iustin Pop
    "TEMPLATE") "select the desired disk template",
258 ce207617 Iustin Pop
   optComplDiskTemplate)
259 c4bb977b Iustin Pop
260 f0753837 René Nussbaumer
oSpindleUse :: OptType
261 ce207617 Iustin Pop
oSpindleUse =
262 ce207617 Iustin Pop
  (Option "" ["spindle-use"]
263 ce207617 Iustin Pop
   (reqWithConversion (tryRead "parsing spindle-use")
264 ce207617 Iustin Pop
    (\su opts -> do
265 ce207617 Iustin Pop
       when (su < 0) $
266 ce207617 Iustin Pop
            fail "Invalid value of the spindle-use (expected >= 0)"
267 ce207617 Iustin Pop
       return $ opts { optSpindleUse = Just su })
268 ce207617 Iustin Pop
    "SPINDLES") "select how many virtual spindle instances use\
269 ce207617 Iustin Pop
                \ [default read from cluster]",
270 ecebe9f6 Iustin Pop
   OptComplFloat)
271 f0753837 René Nussbaumer
272 ddef0585 Guido Trotter
oSelInst :: OptType
273 ce207617 Iustin Pop
oSelInst =
274 ce207617 Iustin Pop
  (Option "" ["select-instances"]
275 ce207617 Iustin Pop
   (ReqArg (\ f opts -> Ok opts { optSelInst = sepSplit ',' f }) "INSTS")
276 ce207617 Iustin Pop
   "only select given instances for any moves",
277 ce207617 Iustin Pop
   OptComplManyInstances)
278 ddef0585 Guido Trotter
279 8fcfb767 Guido Trotter
oInstMoves :: OptType
280 ce207617 Iustin Pop
oInstMoves =
281 ce207617 Iustin Pop
  (Option "" ["no-instance-moves"]
282 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optInstMoves = False}))
283 ce207617 Iustin Pop
   "disallow instance (primary node) moves from the list of allowed,\
284 ce207617 Iustin Pop
   \ instance changes, thus allowing only slower, but sometimes\
285 ce207617 Iustin Pop
   \ safer, drbd secondary changes",
286 ce207617 Iustin Pop
   OptComplNone)
287 8fcfb767 Guido Trotter
288 df18fdfe Iustin Pop
oDynuFile :: OptType
289 ce207617 Iustin Pop
oDynuFile =
290 ce207617 Iustin Pop
  (Option "U" ["dynu-file"]
291 ce207617 Iustin Pop
   (ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
292 ce207617 Iustin Pop
   "Import dynamic utilisation data from the given FILE",
293 ce207617 Iustin Pop
   OptComplFile)
294 0427285d Iustin Pop
295 f0f21ec4 Iustin Pop
oEvacMode :: OptType
296 ce207617 Iustin Pop
oEvacMode =
297 ce207617 Iustin Pop
  (Option "E" ["evac-mode"]
298 ce207617 Iustin Pop
   (NoArg (\opts -> Ok opts { optEvacMode = True }))
299 516c52f2 Dato Simó
   "enable evacuation mode, where the algorithm only moves\
300 ce207617 Iustin Pop
   \ instances away from offline and drained nodes",
301 ce207617 Iustin Pop
   OptComplNone)
302 f0f21ec4 Iustin Pop
303 10f396e1 Iustin Pop
oExInst :: OptType
304 ce207617 Iustin Pop
oExInst =
305 ce207617 Iustin Pop
  (Option "" ["exclude-instances"]
306 ce207617 Iustin Pop
   (ReqArg (\ f opts -> Ok opts { optExInst = sepSplit ',' f }) "INSTS")
307 ce207617 Iustin Pop
   "exclude given instances from any moves",
308 ce207617 Iustin Pop
   OptComplManyInstances)
309 10f396e1 Iustin Pop
310 df18fdfe Iustin Pop
oExTags :: OptType
311 ce207617 Iustin Pop
oExTags =
312 ce207617 Iustin Pop
  (Option "" ["exclusion-tags"]
313 ce207617 Iustin Pop
   (ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
314 ce207617 Iustin Pop
    "TAG,...") "Enable instance exclusion based on given tag prefix",
315 ce207617 Iustin Pop
   OptComplString)
316 0427285d Iustin Pop
317 0df5a1b4 Iustin Pop
oExecJobs :: OptType
318 ce207617 Iustin Pop
oExecJobs =
319 ce207617 Iustin Pop
  (Option "X" ["exec"]
320 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optExecJobs = True}))
321 ce207617 Iustin Pop
   "execute the suggested moves via Luxi (only available when using\
322 ce207617 Iustin Pop
   \ it for data gathering)",
323 ce207617 Iustin Pop
   OptComplNone)
324 0df5a1b4 Iustin Pop
325 7dbe4c72 Klaus Aehlig
oForce :: OptType
326 7dbe4c72 Klaus Aehlig
oForce =
327 7dbe4c72 Klaus Aehlig
  (Option "f" ["force"]
328 7dbe4c72 Klaus Aehlig
   (NoArg (\ opts -> Ok opts {optForce = True}))
329 7dbe4c72 Klaus Aehlig
   "force the execution of this program, even if warnings would\
330 7dbe4c72 Klaus Aehlig
   \ otherwise prevent it",
331 7dbe4c72 Klaus Aehlig
   OptComplNone)
332 7dbe4c72 Klaus Aehlig
333 a423b510 Iustin Pop
oGroup :: OptType
334 ce207617 Iustin Pop
oGroup =
335 ce207617 Iustin Pop
  (Option "G" ["group"]
336 ce207617 Iustin Pop
   (ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
337 0ff01075 Guido Trotter
   "the target node group (name or UUID)",
338 ce207617 Iustin Pop
   OptComplOneGroup)
339 a423b510 Iustin Pop
340 9899796b René Nussbaumer
oIAllocSrc :: OptType
341 ce207617 Iustin Pop
oIAllocSrc =
342 ce207617 Iustin Pop
  (Option "I" ["ialloc-src"]
343 ce207617 Iustin Pop
   (ReqArg (\ f opts -> Ok opts { optIAllocSrc = Just f }) "FILE")
344 ce207617 Iustin Pop
   "Specify an iallocator spec as the cluster data source",
345 ce207617 Iustin Pop
   OptComplFile)
346 9899796b René Nussbaumer
347 8af72964 Dato Simó
oJobDelay :: OptType
348 8af72964 Dato Simó
oJobDelay =
349 8af72964 Dato Simó
  (Option "" ["job-delay"]
350 8af72964 Dato Simó
   (reqWithConversion (tryRead "job delay")
351 8af72964 Dato Simó
    (\d opts -> Ok opts { optJobDelay = d }) "SECONDS")
352 8af72964 Dato Simó
   "insert this much delay before the execution of repair jobs\
353 8af72964 Dato Simó
   \ to allow the tool to continue processing instances",
354 8af72964 Dato Simó
   OptComplFloat)
355 8af72964 Dato Simó
356 29a30533 Iustin Pop
genOLuxiSocket :: String -> OptType
357 29a30533 Iustin Pop
genOLuxiSocket defSocket =
358 ce207617 Iustin Pop
  (Option "L" ["luxi"]
359 ce207617 Iustin Pop
   (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
360 29a30533 Iustin Pop
            fromMaybe defSocket) "SOCKET")
361 29a30533 Iustin Pop
   ("collect data via Luxi, optionally using the given SOCKET path [" ++
362 29a30533 Iustin Pop
    defSocket ++ "]"),
363 ce207617 Iustin Pop
   OptComplFile)
364 0427285d Iustin Pop
365 29a30533 Iustin Pop
oLuxiSocket :: IO OptType
366 67e4fcf4 Iustin Pop
oLuxiSocket = liftM genOLuxiSocket Path.defaultLuxiSocket
367 29a30533 Iustin Pop
368 519edd9f Iustin Pop
oMachineReadable :: OptType
369 ce207617 Iustin Pop
oMachineReadable =
370 ce207617 Iustin Pop
  (Option "" ["machine-readable"]
371 ce207617 Iustin Pop
   (OptArg (\ f opts -> do
372 ce207617 Iustin Pop
              flag <- parseYesNo True f
373 ce207617 Iustin Pop
              return $ opts { optMachineReadable = flag }) "CHOICE")
374 ce207617 Iustin Pop
   "enable machine readable output (pass either 'yes' or 'no' to\
375 ce207617 Iustin Pop
   \ explicitly control the flag, or without an argument defaults to\
376 ce207617 Iustin Pop
   \ yes",
377 ce207617 Iustin Pop
   optComplYesNo)
378 519edd9f Iustin Pop
379 0427285d Iustin Pop
oMaxCpu :: OptType
380 ce207617 Iustin Pop
oMaxCpu =
381 ce207617 Iustin Pop
  (Option "" ["max-cpu"]
382 ce207617 Iustin Pop
   (reqWithConversion (tryRead "parsing max-cpu")
383 ce207617 Iustin Pop
    (\mcpu opts -> do
384 ce207617 Iustin Pop
       when (mcpu <= 0) $
385 ce207617 Iustin Pop
            fail "Invalid value of the max-cpu ratio, expected >0"
386 ce207617 Iustin Pop
       return $ opts { optMcpu = Just mcpu }) "RATIO")
387 ce207617 Iustin Pop
   "maximum virtual-to-physical cpu ratio for nodes (from 0\
388 ce207617 Iustin Pop
   \ upwards) [default read from cluster]",
389 ecebe9f6 Iustin Pop
   OptComplFloat)
390 0427285d Iustin Pop
391 df18fdfe Iustin Pop
oMaxSolLength :: OptType
392 ce207617 Iustin Pop
oMaxSolLength =
393 ce207617 Iustin Pop
  (Option "l" ["max-length"]
394 ce207617 Iustin Pop
   (reqWithConversion (tryRead "max solution length")
395 ce207617 Iustin Pop
    (\i opts -> Ok opts { optMaxLength = i }) "N")
396 516c52f2 Dato Simó
   "cap the solution at this many balancing or allocation\
397 516c52f2 Dato Simó
   \ rounds (useful for very unbalanced clusters or empty\
398 ce207617 Iustin Pop
   \ clusters)",
399 ecebe9f6 Iustin Pop
   OptComplInteger)
400 df18fdfe Iustin Pop
401 0427285d Iustin Pop
oMinDisk :: OptType
402 ce207617 Iustin Pop
oMinDisk =
403 ce207617 Iustin Pop
  (Option "" ["min-disk"]
404 ce207617 Iustin Pop
   (reqWithConversion (tryRead "min free disk space")
405 ce207617 Iustin Pop
    (\n opts -> Ok opts { optMdsk = n }) "RATIO")
406 ce207617 Iustin Pop
   "minimum free disk space for nodes (between 0 and 1) [0]",
407 ecebe9f6 Iustin Pop
   OptComplFloat)
408 0427285d Iustin Pop
409 4f807a57 Iustin Pop
oMinGain :: OptType
410 ce207617 Iustin Pop
oMinGain =
411 ce207617 Iustin Pop
  (Option "g" ["min-gain"]
412 ce207617 Iustin Pop
   (reqWithConversion (tryRead "min gain")
413 ce207617 Iustin Pop
    (\g opts -> Ok opts { optMinGain = g }) "DELTA")
414 ce207617 Iustin Pop
   "minimum gain to aim for in a balancing step before giving up",
415 ecebe9f6 Iustin Pop
   OptComplFloat)
416 4f807a57 Iustin Pop
417 4f807a57 Iustin Pop
oMinGainLim :: OptType
418 ce207617 Iustin Pop
oMinGainLim =
419 ce207617 Iustin Pop
  (Option "" ["min-gain-limit"]
420 ce207617 Iustin Pop
   (reqWithConversion (tryRead "min gain limit")
421 ce207617 Iustin Pop
    (\g opts -> Ok opts { optMinGainLim = g }) "SCORE")
422 ce207617 Iustin Pop
   "minimum cluster score for which we start checking the min-gain",
423 ecebe9f6 Iustin Pop
   OptComplFloat)
424 4f807a57 Iustin Pop
425 df18fdfe Iustin Pop
oMinScore :: OptType
426 ce207617 Iustin Pop
oMinScore =
427 ce207617 Iustin Pop
  (Option "e" ["min-score"]
428 ce207617 Iustin Pop
   (reqWithConversion (tryRead "min score")
429 ce207617 Iustin Pop
    (\e opts -> Ok opts { optMinScore = e }) "EPSILON")
430 ce207617 Iustin Pop
   "mininum score to aim for",
431 ecebe9f6 Iustin Pop
   OptComplFloat)
432 c0501c69 Iustin Pop
433 df18fdfe Iustin Pop
oNoHeaders :: OptType
434 ce207617 Iustin Pop
oNoHeaders =
435 ce207617 Iustin Pop
  (Option "" ["no-headers"]
436 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
437 ce207617 Iustin Pop
   "do not show a header line",
438 ce207617 Iustin Pop
   OptComplNone)
439 4f83a560 Iustin Pop
440 22e513e7 Agata Murawska
oNoSimulation :: OptType
441 ce207617 Iustin Pop
oNoSimulation =
442 ce207617 Iustin Pop
  (Option "" ["no-simulation"]
443 ce207617 Iustin Pop
   (NoArg (\opts -> Ok opts {optNoSimulation = True}))
444 ce207617 Iustin Pop
   "do not perform rebalancing simulation",
445 ce207617 Iustin Pop
   OptComplNone)
446 22e513e7 Agata Murawska
447 df18fdfe Iustin Pop
oNodeSim :: OptType
448 ce207617 Iustin Pop
oNodeSim =
449 ce207617 Iustin Pop
  (Option "" ["simulate"]
450 ce207617 Iustin Pop
   (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
451 ce207617 Iustin Pop
   "simulate an empty cluster, given as\
452 ce207617 Iustin Pop
   \ 'alloc_policy,num_nodes,disk,ram,cpu'",
453 ce207617 Iustin Pop
   OptComplString)
454 df18fdfe Iustin Pop
455 df18fdfe Iustin Pop
oOfflineNode :: OptType
456 ce207617 Iustin Pop
oOfflineNode =
457 ce207617 Iustin Pop
  (Option "O" ["offline"]
458 ce207617 Iustin Pop
   (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
459 ce207617 Iustin Pop
   "set node as offline",
460 ce207617 Iustin Pop
   OptComplOneNode)
461 df18fdfe Iustin Pop
462 df18fdfe Iustin Pop
oOutputDir :: OptType
463 ce207617 Iustin Pop
oOutputDir =
464 ce207617 Iustin Pop
  (Option "d" ["output-dir"]
465 ce207617 Iustin Pop
   (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
466 ce207617 Iustin Pop
   "directory in which to write output files",
467 ce207617 Iustin Pop
   OptComplDir)
468 df18fdfe Iustin Pop
469 df18fdfe Iustin Pop
oPrintCommands :: OptType
470 ce207617 Iustin Pop
oPrintCommands =
471 ce207617 Iustin Pop
  (Option "C" ["print-commands"]
472 ce207617 Iustin Pop
   (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
473 ce207617 Iustin Pop
            fromMaybe "-")
474 ce207617 Iustin Pop
    "FILE")
475 ce207617 Iustin Pop
   "print the ganeti command list for reaching the solution,\
476 ce207617 Iustin Pop
   \ if an argument is passed then write the commands to a\
477 ce207617 Iustin Pop
   \ file named as such",
478 ce207617 Iustin Pop
   OptComplNone)
479 df18fdfe Iustin Pop
480 df18fdfe Iustin Pop
oPrintInsts :: OptType
481 ce207617 Iustin Pop
oPrintInsts =
482 ce207617 Iustin Pop
  (Option "" ["print-instances"]
483 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optShowInsts = True }))
484 ce207617 Iustin Pop
   "print the final instance map",
485 ce207617 Iustin Pop
   OptComplNone)
486 df18fdfe Iustin Pop
487 df18fdfe Iustin Pop
oPrintNodes :: OptType
488 ce207617 Iustin Pop
oPrintNodes =
489 ce207617 Iustin Pop
  (Option "p" ["print-nodes"]
490 ce207617 Iustin Pop
   (OptArg ((\ f opts ->
491 ce207617 Iustin Pop
               let (prefix, realf) = case f of
492 ce207617 Iustin Pop
                                       '+':rest -> (["+"], rest)
493 ce207617 Iustin Pop
                                       _ -> ([], f)
494 ce207617 Iustin Pop
                   splitted = prefix ++ sepSplit ',' realf
495 ce207617 Iustin Pop
               in Ok opts { optShowNodes = Just splitted }) .
496 ce207617 Iustin Pop
            fromMaybe []) "FIELDS")
497 ce207617 Iustin Pop
   "print the final node list",
498 ce207617 Iustin Pop
   OptComplNone)
499 df18fdfe Iustin Pop
500 df18fdfe Iustin Pop
oQuiet :: OptType
501 ce207617 Iustin Pop
oQuiet =
502 ce207617 Iustin Pop
  (Option "q" ["quiet"]
503 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
504 ce207617 Iustin Pop
   "decrease the verbosity level",
505 ce207617 Iustin Pop
   OptComplNone)
506 df18fdfe Iustin Pop
507 df18fdfe Iustin Pop
oRapiMaster :: OptType
508 ce207617 Iustin Pop
oRapiMaster =
509 ce207617 Iustin Pop
  (Option "m" ["master"]
510 ce207617 Iustin Pop
   (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
511 ce207617 Iustin Pop
   "collect data via RAPI at the given ADDRESS",
512 ce207617 Iustin Pop
   OptComplHost)
513 df18fdfe Iustin Pop
514 02da9d07 Iustin Pop
oSaveCluster :: OptType
515 ce207617 Iustin Pop
oSaveCluster =
516 ce207617 Iustin Pop
  (Option "S" ["save"]
517 ce207617 Iustin Pop
   (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
518 ce207617 Iustin Pop
   "Save cluster state at the end of the processing to FILE",
519 ce207617 Iustin Pop
   OptComplNone)
520 02da9d07 Iustin Pop
521 294bb337 Iustin Pop
oStdSpec :: OptType
522 ce207617 Iustin Pop
oStdSpec =
523 ce207617 Iustin Pop
  (Option "" ["standard-alloc"]
524 ce207617 Iustin Pop
   (ReqArg (\ inp opts -> do
525 ce207617 Iustin Pop
              tspec <- parseISpecString "standard" inp
526 ce207617 Iustin Pop
              return $ opts { optStdSpec = Just tspec } )
527 ce207617 Iustin Pop
    "STDSPEC")
528 ce207617 Iustin Pop
   "enable standard specs allocation, given as 'disk,ram,cpu'",
529 ce207617 Iustin Pop
   OptComplString)
530 294bb337 Iustin Pop
531 1f9066c0 Iustin Pop
oTieredSpec :: OptType
532 ce207617 Iustin Pop
oTieredSpec =
533 ce207617 Iustin Pop
  (Option "" ["tiered-alloc"]
534 ce207617 Iustin Pop
   (ReqArg (\ inp opts -> do
535 ce207617 Iustin Pop
              tspec <- parseISpecString "tiered" inp
536 ce207617 Iustin Pop
              return $ opts { optTieredSpec = Just tspec } )
537 ce207617 Iustin Pop
    "TSPEC")
538 ce207617 Iustin Pop
   "enable tiered specs allocation, given as 'disk,ram,cpu'",
539 ce207617 Iustin Pop
   OptComplString)
540 1f9066c0 Iustin Pop
541 df18fdfe Iustin Pop
oVerbose :: OptType
542 ce207617 Iustin Pop
oVerbose =
543 ce207617 Iustin Pop
  (Option "v" ["verbose"]
544 ce207617 Iustin Pop
   (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
545 ce207617 Iustin Pop
   "increase the verbosity level",
546 ce207617 Iustin Pop
   OptComplNone)
547 fae371cc Iustin Pop
548 e247747c Iustin Pop
oPriority :: OptType
549 e247747c Iustin Pop
oPriority =
550 e247747c Iustin Pop
  (Option "" ["priority"]
551 e247747c Iustin Pop
   (ReqArg (\ inp opts -> do
552 e247747c Iustin Pop
              prio <- parseSubmitPriority inp
553 e247747c Iustin Pop
              Ok opts { optPriority = Just prio }) "PRIO")
554 e247747c Iustin Pop
   "set the priority of submitted jobs",
555 e247747c Iustin Pop
    OptComplChoices (map fmtSubmitPriority [minBound..maxBound]))
556 e247747c Iustin Pop
557 42834645 Iustin Pop
-- | Generic options.
558 42834645 Iustin Pop
genericOpts :: [GenericOptType Options]
559 42834645 Iustin Pop
genericOpts =  [ oShowVer
560 42834645 Iustin Pop
               , oShowHelp
561 097ad7ee Iustin Pop
               , oShowComp
562 42834645 Iustin Pop
               ]
563 42834645 Iustin Pop
564 525bfb36 Iustin Pop
-- * Functions
565 525bfb36 Iustin Pop
566 51000365 Iustin Pop
-- | Wrapper over 'Common.parseOpts' with our custom options.
567 0427285d Iustin Pop
parseOpts :: [String]               -- ^ The command line arguments
568 0427285d Iustin Pop
          -> String                 -- ^ The program name
569 0427285d Iustin Pop
          -> [OptType]              -- ^ The supported command line options
570 22278fa7 Iustin Pop
          -> [ArgCompletion]        -- ^ The supported command line arguments
571 0427285d Iustin Pop
          -> IO (Options, [String]) -- ^ The resulting options and leftover
572 0427285d Iustin Pop
                                    -- arguments
573 51000365 Iustin Pop
parseOpts = Common.parseOpts defaultOptions
574 51000365 Iustin Pop
575 209b3711 Iustin Pop
576 9188aeef Iustin Pop
-- | A shell script template for autogenerated scripts.
577 e0eb63f0 Iustin Pop
shTemplate :: String
578 e0eb63f0 Iustin Pop
shTemplate =
579 cd08cfa4 Iustin Pop
  printf "#!/bin/sh\n\n\
580 cd08cfa4 Iustin Pop
         \# Auto-generated script for executing cluster rebalancing\n\n\
581 cd08cfa4 Iustin Pop
         \# To stop, touch the file /tmp/stop-htools\n\n\
582 cd08cfa4 Iustin Pop
         \set -e\n\n\
583 cd08cfa4 Iustin Pop
         \check() {\n\
584 cd08cfa4 Iustin Pop
         \  if [ -f /tmp/stop-htools ]; then\n\
585 cd08cfa4 Iustin Pop
         \    echo 'Stop requested, exiting'\n\
586 cd08cfa4 Iustin Pop
         \    exit 0\n\
587 cd08cfa4 Iustin Pop
         \  fi\n\
588 cd08cfa4 Iustin Pop
         \}\n\n"
589 417f6b50 Iustin Pop
590 417f6b50 Iustin Pop
-- | Optionally print the node list.
591 417f6b50 Iustin Pop
maybePrintNodes :: Maybe [String]       -- ^ The field list
592 417f6b50 Iustin Pop
                -> String               -- ^ Informational message
593 417f6b50 Iustin Pop
                -> ([String] -> String) -- ^ Function to generate the listing
594 417f6b50 Iustin Pop
                -> IO ()
595 417f6b50 Iustin Pop
maybePrintNodes Nothing _ _ = return ()
596 417f6b50 Iustin Pop
maybePrintNodes (Just fields) msg fn = do
597 417f6b50 Iustin Pop
  hPutStrLn stderr ""
598 417f6b50 Iustin Pop
  hPutStrLn stderr (msg ++ " status:")
599 417f6b50 Iustin Pop
  hPutStrLn stderr $ fn fields
600 33e44f0c Iustin Pop
601 33e44f0c Iustin Pop
-- | Optionally print the instance list.
602 33e44f0c Iustin Pop
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
603 33e44f0c Iustin Pop
                -> String -- ^ Type of the instance map (e.g. initial)
604 33e44f0c Iustin Pop
                -> String -- ^ The instance data
605 33e44f0c Iustin Pop
                -> IO ()
606 33e44f0c Iustin Pop
maybePrintInsts do_print msg instdata =
607 33e44f0c Iustin Pop
  when do_print $ do
608 33e44f0c Iustin Pop
    hPutStrLn stderr ""
609 33e44f0c Iustin Pop
    hPutStrLn stderr $ msg ++ " instance map:"
610 33e44f0c Iustin Pop
    hPutStr stderr instdata
611 8cd36391 Iustin Pop
612 8cd36391 Iustin Pop
-- | Function to display warning messages from parsing the cluster
613 8cd36391 Iustin Pop
-- state.
614 8cd36391 Iustin Pop
maybeShowWarnings :: [String] -- ^ The warning messages
615 8cd36391 Iustin Pop
                  -> IO ()
616 8cd36391 Iustin Pop
maybeShowWarnings fix_msgs =
617 8cd36391 Iustin Pop
  unless (null fix_msgs) $ do
618 8cd36391 Iustin Pop
    hPutStrLn stderr "Warning: cluster has inconsistent data:"
619 8cd36391 Iustin Pop
    hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
620 5296ee23 Iustin Pop
621 79eef90b Agata Murawska
-- | Format a list of key, value as a shell fragment.
622 e60fa4af Agata Murawska
printKeys :: String              -- ^ Prefix to printed variables
623 e60fa4af Agata Murawska
          -> [(String, String)]  -- ^ List of (key, value) pairs to be printed
624 e60fa4af Agata Murawska
          -> IO ()
625 51000365 Iustin Pop
printKeys prefix =
626 51000365 Iustin Pop
  mapM_ (\(k, v) ->
627 51000365 Iustin Pop
           printf "%s_%s=%s\n" prefix (map toUpper k) (ensureQuoted v))
628 79eef90b Agata Murawska
629 79eef90b Agata Murawska
-- | Prints the final @OK@ marker in machine readable output.
630 e60fa4af Agata Murawska
printFinal :: String    -- ^ Prefix to printed variable
631 51000365 Iustin Pop
           -> Bool      -- ^ Whether output should be machine readable;
632 51000365 Iustin Pop
                        -- note: if not, there is nothing to print
633 e60fa4af Agata Murawska
           -> IO ()
634 79eef90b Agata Murawska
printFinal prefix True =
635 79eef90b Agata Murawska
  -- this should be the final entry
636 79eef90b Agata Murawska
  printKeys prefix [("OK", "1")]
637 79eef90b Agata Murawska
638 79eef90b Agata Murawska
printFinal _ False = return ()
639 79eef90b Agata Murawska
640 284e9822 Iustin Pop
-- | Potentially set the node as offline based on passed offline list.
641 284e9822 Iustin Pop
setNodeOffline :: [Ndx] -> Node.Node -> Node.Node
642 284e9822 Iustin Pop
setNodeOffline offline_indices n =
643 284e9822 Iustin Pop
  if Node.idx n `elem` offline_indices
644 284e9822 Iustin Pop
    then Node.setOffline n True
645 284e9822 Iustin Pop
    else n
646 284e9822 Iustin Pop
647 5296ee23 Iustin Pop
-- | Set node properties based on command line options.
648 5296ee23 Iustin Pop
setNodeStatus :: Options -> Node.List -> IO Node.List
649 5296ee23 Iustin Pop
setNodeStatus opts fixed_nl = do
650 5296ee23 Iustin Pop
  let offline_passed = optOffline opts
651 5296ee23 Iustin Pop
      all_nodes = Container.elems fixed_nl
652 5296ee23 Iustin Pop
      offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
653 5296ee23 Iustin Pop
      offline_wrong = filter (not . goodLookupResult) offline_lkp
654 5296ee23 Iustin Pop
      offline_names = map lrContent offline_lkp
655 5296ee23 Iustin Pop
      offline_indices = map Node.idx $
656 5296ee23 Iustin Pop
                        filter (\n -> Node.name n `elem` offline_names)
657 5296ee23 Iustin Pop
                               all_nodes
658 5296ee23 Iustin Pop
      m_cpu = optMcpu opts
659 5296ee23 Iustin Pop
      m_dsk = optMdsk opts
660 5296ee23 Iustin Pop
661 5b11f8db Iustin Pop
  unless (null offline_wrong) .
662 88a10df5 Iustin Pop
         exitErr $ printf "wrong node name(s) set as offline: %s\n"
663 88a10df5 Iustin Pop
                   (commaJoin (map lrContent offline_wrong))
664 284e9822 Iustin Pop
  let setMCpuFn = case m_cpu of
665 284e9822 Iustin Pop
                    Nothing -> id
666 284e9822 Iustin Pop
                    Just new_mcpu -> flip Node.setMcpu new_mcpu
667 284e9822 Iustin Pop
  let nm = Container.map (setNodeOffline offline_indices .
668 284e9822 Iustin Pop
                          flip Node.setMdsk m_dsk .
669 284e9822 Iustin Pop
                          setMCpuFn) fixed_nl
670 284e9822 Iustin Pop
  return nm