Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / HTools / CLI.hs @ 2d6bdcc5

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