Statistics
| Branch: | Tag: | Revision:

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

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