Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / CLI.hs @ 9515a7d2

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