Statistics
| Branch: | Tag: | Revision:

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

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