Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / CLI.hs @ 07e68848

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