Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / CLI.hs @ 89363f98

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