Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ ee4ffc8a

History | View | Annotate | Download (20.7 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 525bfb36 Iustin Pop
binaries, separated into this module since "Ganeti.HTools.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 cd08cfa4 Iustin Pop
  , parseOpts
34 51c3d88f Iustin Pop
  , parseOptsInner
35 a7ea861a Iustin Pop
  , parseYesNo
36 8b5a517a Iustin Pop
  , parseISpecString
37 cd08cfa4 Iustin Pop
  , shTemplate
38 cd08cfa4 Iustin Pop
  , defaultLuxiSocket
39 cd08cfa4 Iustin Pop
  , maybePrintNodes
40 cd08cfa4 Iustin Pop
  , maybePrintInsts
41 cd08cfa4 Iustin Pop
  , maybeShowWarnings
42 cd08cfa4 Iustin Pop
  , setNodeStatus
43 cd08cfa4 Iustin Pop
  -- * The options
44 cd08cfa4 Iustin Pop
  , oDataFile
45 cd08cfa4 Iustin Pop
  , oDiskMoves
46 cd08cfa4 Iustin Pop
  , oDiskTemplate
47 cd08cfa4 Iustin Pop
  , oDynuFile
48 cd08cfa4 Iustin Pop
  , oEvacMode
49 cd08cfa4 Iustin Pop
  , oExInst
50 cd08cfa4 Iustin Pop
  , oExTags
51 cd08cfa4 Iustin Pop
  , oExecJobs
52 cd08cfa4 Iustin Pop
  , oGroup
53 cd08cfa4 Iustin Pop
  , oInstMoves
54 cd08cfa4 Iustin Pop
  , oLuxiSocket
55 cd08cfa4 Iustin Pop
  , oMachineReadable
56 cd08cfa4 Iustin Pop
  , oMaxCpu
57 cd08cfa4 Iustin Pop
  , oMaxSolLength
58 cd08cfa4 Iustin Pop
  , oMinDisk
59 cd08cfa4 Iustin Pop
  , oMinGain
60 cd08cfa4 Iustin Pop
  , oMinGainLim
61 cd08cfa4 Iustin Pop
  , oMinScore
62 cd08cfa4 Iustin Pop
  , oNoHeaders
63 cd08cfa4 Iustin Pop
  , oNodeSim
64 cd08cfa4 Iustin Pop
  , oOfflineNode
65 cd08cfa4 Iustin Pop
  , oOutputDir
66 cd08cfa4 Iustin Pop
  , oPrintCommands
67 cd08cfa4 Iustin Pop
  , oPrintInsts
68 cd08cfa4 Iustin Pop
  , oPrintNodes
69 cd08cfa4 Iustin Pop
  , oQuiet
70 cd08cfa4 Iustin Pop
  , oRapiMaster
71 cd08cfa4 Iustin Pop
  , oReplay
72 cd08cfa4 Iustin Pop
  , oSaveCluster
73 cd08cfa4 Iustin Pop
  , oSelInst
74 cd08cfa4 Iustin Pop
  , oShowHelp
75 cd08cfa4 Iustin Pop
  , oShowVer
76 294bb337 Iustin Pop
  , oStdSpec
77 ee4ffc8a Iustin Pop
  , oTestCount
78 cd08cfa4 Iustin Pop
  , oTieredSpec
79 cd08cfa4 Iustin Pop
  , oVerbose
80 cd08cfa4 Iustin Pop
  ) where
81 209b3711 Iustin Pop
82 cc532bdd Iustin Pop
import Control.Monad
83 e8f89bb6 Iustin Pop
import Data.Maybe (fromMaybe)
84 8e445e6d Iustin Pop
import qualified Data.Version
85 209b3711 Iustin Pop
import System.Console.GetOpt
86 209b3711 Iustin Pop
import System.IO
87 209b3711 Iustin Pop
import System.Info
88 7345b69b Iustin Pop
import System.Exit
89 5296ee23 Iustin Pop
import Text.Printf (printf, hPrintf)
90 209b3711 Iustin Pop
91 209b3711 Iustin Pop
import qualified Ganeti.HTools.Version as Version(version)
92 5296ee23 Iustin Pop
import qualified Ganeti.HTools.Container as Container
93 5296ee23 Iustin Pop
import qualified Ganeti.HTools.Node as Node
94 a69ff623 Iustin Pop
import qualified Ganeti.Constants as C
95 92e32d76 Iustin Pop
import Ganeti.HTools.Types
96 1f9066c0 Iustin Pop
import Ganeti.HTools.Utils
97 5296ee23 Iustin Pop
import Ganeti.HTools.Loader
98 fae371cc Iustin Pop
99 525bfb36 Iustin Pop
-- * Constants
100 525bfb36 Iustin Pop
101 525bfb36 Iustin Pop
-- | The default value for the luxi socket.
102 525bfb36 Iustin Pop
--
103 525bfb36 Iustin Pop
-- This is re-exported from the "Ganeti.Constants" module.
104 8e445e6d Iustin Pop
defaultLuxiSocket :: FilePath
105 a69ff623 Iustin Pop
defaultLuxiSocket = C.masterSocket
106 8e445e6d Iustin Pop
107 525bfb36 Iustin Pop
-- * Data types
108 525bfb36 Iustin Pop
109 0427285d Iustin Pop
-- | Command line options structure.
110 0427285d Iustin Pop
data Options = Options
111 cd08cfa4 Iustin Pop
  { optDataFile    :: Maybe FilePath -- ^ Path to the cluster data file
112 cd08cfa4 Iustin Pop
  , optDiskMoves   :: Bool           -- ^ Allow disk moves
113 cd08cfa4 Iustin Pop
  , optInstMoves   :: Bool           -- ^ Allow instance moves
114 9fdd3d0f Iustin Pop
  , optDiskTemplate :: Maybe DiskTemplate  -- ^ Override for the disk template
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 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 cd08cfa4 Iustin Pop
  , optNodeSim     :: [String]       -- ^ Cluster simulation mode
133 cd08cfa4 Iustin Pop
  , optOffline     :: [String]       -- ^ Names of offline nodes
134 cd08cfa4 Iustin Pop
  , optOutPath     :: FilePath       -- ^ Path to the output directory
135 cd08cfa4 Iustin Pop
  , optSaveCluster :: Maybe FilePath -- ^ Save cluster state to this file
136 cd08cfa4 Iustin Pop
  , optShowCmds    :: Maybe FilePath -- ^ Whether to show the command list
137 cd08cfa4 Iustin Pop
  , optShowHelp    :: Bool           -- ^ Just show the help
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 cd08cfa4 Iustin Pop
  , optDynuFile    = Nothing
156 cd08cfa4 Iustin Pop
  , optEvacMode    = False
157 cd08cfa4 Iustin Pop
  , optExInst      = []
158 cd08cfa4 Iustin Pop
  , optExTags      = Nothing
159 cd08cfa4 Iustin Pop
  , optExecJobs    = False
160 cd08cfa4 Iustin Pop
  , optGroup       = Nothing
161 cd08cfa4 Iustin Pop
  , optSelInst     = []
162 cd08cfa4 Iustin Pop
  , optLuxi        = Nothing
163 cd08cfa4 Iustin Pop
  , optMachineReadable = False
164 cd08cfa4 Iustin Pop
  , optMaster      = ""
165 cd08cfa4 Iustin Pop
  , optMaxLength   = -1
166 284e9822 Iustin Pop
  , optMcpu        = Nothing
167 cd08cfa4 Iustin Pop
  , optMdsk        = defReservedDiskRatio
168 cd08cfa4 Iustin Pop
  , optMinGain     = 1e-2
169 cd08cfa4 Iustin Pop
  , optMinGainLim  = 1e-1
170 cd08cfa4 Iustin Pop
  , optMinScore    = 1e-9
171 cd08cfa4 Iustin Pop
  , optNoHeaders   = False
172 cd08cfa4 Iustin Pop
  , optNodeSim     = []
173 cd08cfa4 Iustin Pop
  , optOffline     = []
174 cd08cfa4 Iustin Pop
  , optOutPath     = "."
175 cd08cfa4 Iustin Pop
  , optSaveCluster = Nothing
176 cd08cfa4 Iustin Pop
  , optShowCmds    = Nothing
177 cd08cfa4 Iustin Pop
  , optShowHelp    = False
178 cd08cfa4 Iustin Pop
  , optShowInsts   = False
179 cd08cfa4 Iustin Pop
  , optShowNodes   = Nothing
180 cd08cfa4 Iustin Pop
  , optShowVer     = False
181 be468da0 Iustin Pop
  , optStdSpec     = Nothing
182 ee4ffc8a Iustin Pop
  , optTestCount   = Nothing
183 cd08cfa4 Iustin Pop
  , optTieredSpec  = Nothing
184 cd08cfa4 Iustin Pop
  , optReplay      = Nothing
185 cd08cfa4 Iustin Pop
  , optVerbose     = 1
186 cd08cfa4 Iustin Pop
  }
187 0427285d Iustin Pop
188 525bfb36 Iustin Pop
-- | Abrreviation for the option type.
189 2f567ac0 Iustin Pop
type OptType = OptDescr (Options -> Result Options)
190 0427285d Iustin Pop
191 7da760ca Iustin Pop
-- * Helper functions
192 7da760ca Iustin Pop
193 7da760ca Iustin Pop
parseISpecString :: String -> String -> Result RSpec
194 7da760ca Iustin Pop
parseISpecString descr inp = do
195 7da760ca Iustin Pop
  let sp = sepSplit ',' inp
196 8b5a517a Iustin Pop
      err = Bad ("Invalid " ++ descr ++ " specification: '" ++ inp ++
197 8b5a517a Iustin Pop
                 "', expected disk,ram,cpu")
198 8b5a517a Iustin Pop
  when (length sp /= 3) err
199 7da760ca Iustin Pop
  prs <- mapM (\(fn, val) -> fn val) $
200 8b5a517a Iustin Pop
         zip [ annotateResult (descr ++ " specs disk") . parseUnit
201 8b5a517a Iustin Pop
             , annotateResult (descr ++ " specs memory") . parseUnit
202 7da760ca Iustin Pop
             , tryRead (descr ++ " specs cpus")
203 7da760ca Iustin Pop
             ] sp
204 7da760ca Iustin Pop
  case prs of
205 7da760ca Iustin Pop
    [dsk, ram, cpu] -> return $ RSpec cpu ram dsk
206 8b5a517a Iustin Pop
    _ -> err
207 7da760ca Iustin Pop
208 525bfb36 Iustin Pop
-- * Command line options
209 525bfb36 Iustin Pop
210 16c2369c Iustin Pop
oDataFile :: OptType
211 16c2369c Iustin Pop
oDataFile = Option "t" ["text-data"]
212 16c2369c Iustin Pop
            (ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
213 16c2369c Iustin Pop
            "the cluster data FILE"
214 0427285d Iustin Pop
215 df18fdfe Iustin Pop
oDiskMoves :: OptType
216 df18fdfe Iustin Pop
oDiskMoves = Option "" ["no-disk-moves"]
217 df18fdfe Iustin Pop
             (NoArg (\ opts -> Ok opts { optDiskMoves = False}))
218 df18fdfe Iustin Pop
             "disallow disk moves from the list of allowed instance changes,\
219 df18fdfe Iustin Pop
             \ thus allowing only the 'cheap' failover/migrate operations"
220 b2278348 Iustin Pop
221 c4bb977b Iustin Pop
oDiskTemplate :: OptType
222 c4bb977b Iustin Pop
oDiskTemplate = Option "" ["disk-template"]
223 c4bb977b Iustin Pop
                (ReqArg (\ t opts -> do
224 5f828ce4 Agata Murawska
                           dt <- diskTemplateFromRaw t
225 9fdd3d0f Iustin Pop
                           return $ opts { optDiskTemplate = Just dt })
226 9fdd3d0f Iustin Pop
                 "TEMPLATE") "select the desired disk template"
227 c4bb977b Iustin Pop
228 ddef0585 Guido Trotter
oSelInst :: OptType
229 ddef0585 Guido Trotter
oSelInst = Option "" ["select-instances"]
230 ddef0585 Guido Trotter
          (ReqArg (\ f opts -> Ok opts { optSelInst = sepSplit ',' f }) "INSTS")
231 ddef0585 Guido Trotter
          "only select given instances for any moves"
232 ddef0585 Guido Trotter
233 8fcfb767 Guido Trotter
oInstMoves :: OptType
234 8fcfb767 Guido Trotter
oInstMoves = Option "" ["no-instance-moves"]
235 8fcfb767 Guido Trotter
             (NoArg (\ opts -> Ok opts { optInstMoves = False}))
236 8fcfb767 Guido Trotter
             "disallow instance (primary node) moves from the list of allowed,\
237 8fcfb767 Guido Trotter
             \ instance changes, thus allowing only slower, but sometimes\
238 8fcfb767 Guido Trotter
             \ safer, drbd secondary changes"
239 8fcfb767 Guido Trotter
240 df18fdfe Iustin Pop
oDynuFile :: OptType
241 df18fdfe Iustin Pop
oDynuFile = Option "U" ["dynu-file"]
242 df18fdfe Iustin Pop
            (ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
243 df18fdfe Iustin Pop
            "Import dynamic utilisation data from the given FILE"
244 0427285d Iustin Pop
245 f0f21ec4 Iustin Pop
oEvacMode :: OptType
246 f0f21ec4 Iustin Pop
oEvacMode = Option "E" ["evac-mode"]
247 f0f21ec4 Iustin Pop
            (NoArg (\opts -> Ok opts { optEvacMode = True }))
248 f0f21ec4 Iustin Pop
            "enable evacuation mode, where the algorithm only moves \
249 f0f21ec4 Iustin Pop
            \ instances away from offline and drained nodes"
250 f0f21ec4 Iustin Pop
251 10f396e1 Iustin Pop
oExInst :: OptType
252 10f396e1 Iustin Pop
oExInst = Option "" ["exclude-instances"]
253 10f396e1 Iustin Pop
          (ReqArg (\ f opts -> Ok opts { optExInst = sepSplit ',' f }) "INSTS")
254 6c30ce16 Guido Trotter
          "exclude given instances from any moves"
255 10f396e1 Iustin Pop
256 df18fdfe Iustin Pop
oExTags :: OptType
257 df18fdfe Iustin Pop
oExTags = Option "" ["exclusion-tags"]
258 df18fdfe Iustin Pop
            (ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
259 df18fdfe Iustin Pop
             "TAG,...") "Enable instance exclusion based on given tag prefix"
260 0427285d Iustin Pop
261 0df5a1b4 Iustin Pop
oExecJobs :: OptType
262 0df5a1b4 Iustin Pop
oExecJobs = Option "X" ["exec"]
263 2f567ac0 Iustin Pop
             (NoArg (\ opts -> Ok opts { optExecJobs = True}))
264 0df5a1b4 Iustin Pop
             "execute the suggested moves via Luxi (only available when using\
265 71e635f3 Renรฉ Nussbaumer
             \ it for data gathering)"
266 0df5a1b4 Iustin Pop
267 a423b510 Iustin Pop
oGroup :: OptType
268 a423b510 Iustin Pop
oGroup = Option "G" ["group"]
269 a423b510 Iustin Pop
            (ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
270 a423b510 Iustin Pop
            "the ID of the group to balance"
271 a423b510 Iustin Pop
272 df18fdfe Iustin Pop
oLuxiSocket :: OptType
273 df18fdfe Iustin Pop
oLuxiSocket = Option "L" ["luxi"]
274 df18fdfe Iustin Pop
              (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
275 df18fdfe Iustin Pop
                       fromMaybe defaultLuxiSocket) "SOCKET")
276 df18fdfe Iustin Pop
              "collect data via Luxi, optionally using the given SOCKET path"
277 0427285d Iustin Pop
278 519edd9f Iustin Pop
oMachineReadable :: OptType
279 519edd9f Iustin Pop
oMachineReadable = Option "" ["machine-readable"]
280 cd08cfa4 Iustin Pop
                   (OptArg (\ f opts -> do
281 519edd9f Iustin Pop
                     flag <- parseYesNo True f
282 519edd9f Iustin Pop
                     return $ opts { optMachineReadable = flag }) "CHOICE")
283 519edd9f Iustin Pop
          "enable machine readable output (pass either 'yes' or 'no' to\
284 519edd9f Iustin Pop
          \ explicitely control the flag, or without an argument defaults to\
285 519edd9f Iustin Pop
          \ yes"
286 519edd9f Iustin Pop
287 0427285d Iustin Pop
oMaxCpu :: OptType
288 0427285d Iustin Pop
oMaxCpu = Option "" ["max-cpu"]
289 284e9822 Iustin Pop
          (ReqArg (\ n opts -> do
290 284e9822 Iustin Pop
                     mcpu <- tryRead "parsing max-cpu" n
291 284e9822 Iustin Pop
                     when (mcpu <= 0) $
292 284e9822 Iustin Pop
                          fail "Invalid value of the max-cpu ratio,\
293 284e9822 Iustin Pop
                               \ expected >0"
294 284e9822 Iustin Pop
                     return $ opts { optMcpu = Just mcpu }) "RATIO")
295 284e9822 Iustin Pop
          "maximum virtual-to-physical cpu ratio for nodes (from 0\
296 284e9822 Iustin Pop
          \ upwards) [default read from cluster]"
297 0427285d Iustin Pop
298 df18fdfe Iustin Pop
oMaxSolLength :: OptType
299 df18fdfe Iustin Pop
oMaxSolLength = Option "l" ["max-length"]
300 df18fdfe Iustin Pop
                (ReqArg (\ i opts -> Ok opts { optMaxLength = read i }) "N")
301 b8a2c0ab Iustin Pop
                "cap the solution at this many balancing or allocation \
302 b8a2c0ab Iustin Pop
                \ rounds (useful for very unbalanced clusters or empty \
303 b8a2c0ab Iustin Pop
                \ clusters)"
304 df18fdfe Iustin Pop
305 0427285d Iustin Pop
oMinDisk :: OptType
306 0427285d Iustin Pop
oMinDisk = Option "" ["min-disk"]
307 2f567ac0 Iustin Pop
           (ReqArg (\ n opts -> Ok opts { optMdsk = read n }) "RATIO")
308 f4c0b8c5 Iustin Pop
           "minimum free disk space for nodes (between 0 and 1) [0]"
309 0427285d Iustin Pop
310 4f807a57 Iustin Pop
oMinGain :: OptType
311 4f807a57 Iustin Pop
oMinGain = Option "g" ["min-gain"]
312 4f807a57 Iustin Pop
            (ReqArg (\ g opts -> Ok opts { optMinGain = read g }) "DELTA")
313 4f807a57 Iustin Pop
            "minimum gain to aim for in a balancing step before giving up"
314 4f807a57 Iustin Pop
315 4f807a57 Iustin Pop
oMinGainLim :: OptType
316 4f807a57 Iustin Pop
oMinGainLim = Option "" ["min-gain-limit"]
317 4f807a57 Iustin Pop
            (ReqArg (\ g opts -> Ok opts { optMinGainLim = read g }) "SCORE")
318 4f807a57 Iustin Pop
            "minimum cluster score for which we start checking the min-gain"
319 4f807a57 Iustin Pop
320 df18fdfe Iustin Pop
oMinScore :: OptType
321 df18fdfe Iustin Pop
oMinScore = Option "e" ["min-score"]
322 df18fdfe Iustin Pop
            (ReqArg (\ e opts -> Ok opts { optMinScore = read e }) "EPSILON")
323 4f807a57 Iustin Pop
            "mininum score to aim for"
324 c0501c69 Iustin Pop
325 df18fdfe Iustin Pop
oNoHeaders :: OptType
326 df18fdfe Iustin Pop
oNoHeaders = Option "" ["no-headers"]
327 df18fdfe Iustin Pop
             (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
328 df18fdfe Iustin Pop
             "do not show a header line"
329 4f83a560 Iustin Pop
330 df18fdfe Iustin Pop
oNodeSim :: OptType
331 df18fdfe Iustin Pop
oNodeSim = Option "" ["simulate"]
332 9983063b Iustin Pop
            (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
333 df18fdfe Iustin Pop
            "simulate an empty cluster, given as 'num_nodes,disk,ram,cpu'"
334 df18fdfe Iustin Pop
335 df18fdfe Iustin Pop
oOfflineNode :: OptType
336 df18fdfe Iustin Pop
oOfflineNode = Option "O" ["offline"]
337 df18fdfe Iustin Pop
               (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
338 df18fdfe Iustin Pop
               "set node as offline"
339 df18fdfe Iustin Pop
340 df18fdfe Iustin Pop
oOutputDir :: OptType
341 df18fdfe Iustin Pop
oOutputDir = Option "d" ["output-dir"]
342 df18fdfe Iustin Pop
             (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
343 df18fdfe Iustin Pop
             "directory in which to write output files"
344 df18fdfe Iustin Pop
345 df18fdfe Iustin Pop
oPrintCommands :: OptType
346 df18fdfe Iustin Pop
oPrintCommands = Option "C" ["print-commands"]
347 df18fdfe Iustin Pop
                 (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
348 df18fdfe Iustin Pop
                          fromMaybe "-")
349 df18fdfe Iustin Pop
                  "FILE")
350 df18fdfe Iustin Pop
                 "print the ganeti command list for reaching the solution,\
351 df18fdfe Iustin Pop
                 \ if an argument is passed then write the commands to a\
352 df18fdfe Iustin Pop
                 \ file named as such"
353 df18fdfe Iustin Pop
354 df18fdfe Iustin Pop
oPrintInsts :: OptType
355 df18fdfe Iustin Pop
oPrintInsts = Option "" ["print-instances"]
356 df18fdfe Iustin Pop
              (NoArg (\ opts -> Ok opts { optShowInsts = True }))
357 df18fdfe Iustin Pop
              "print the final instance map"
358 df18fdfe Iustin Pop
359 df18fdfe Iustin Pop
oPrintNodes :: OptType
360 df18fdfe Iustin Pop
oPrintNodes = Option "p" ["print-nodes"]
361 df18fdfe Iustin Pop
              (OptArg ((\ f opts ->
362 cd08cfa4 Iustin Pop
                          let (prefix, realf) = case f of
363 cd08cfa4 Iustin Pop
                                                  '+':rest -> (["+"], rest)
364 cd08cfa4 Iustin Pop
                                                  _ -> ([], f)
365 cd08cfa4 Iustin Pop
                              splitted = prefix ++ sepSplit ',' realf
366 cd08cfa4 Iustin Pop
                          in Ok opts { optShowNodes = Just splitted }) .
367 df18fdfe Iustin Pop
                       fromMaybe []) "FIELDS")
368 df18fdfe Iustin Pop
              "print the final node list"
369 df18fdfe Iustin Pop
370 df18fdfe Iustin Pop
oQuiet :: OptType
371 df18fdfe Iustin Pop
oQuiet = Option "q" ["quiet"]
372 df18fdfe Iustin Pop
         (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
373 df18fdfe Iustin Pop
         "decrease the verbosity level"
374 df18fdfe Iustin Pop
375 df18fdfe Iustin Pop
oRapiMaster :: OptType
376 df18fdfe Iustin Pop
oRapiMaster = Option "m" ["master"]
377 df18fdfe Iustin Pop
              (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
378 df18fdfe Iustin Pop
              "collect data via RAPI at the given ADDRESS"
379 df18fdfe Iustin Pop
380 02da9d07 Iustin Pop
oSaveCluster :: OptType
381 02da9d07 Iustin Pop
oSaveCluster = Option "S" ["save"]
382 02da9d07 Iustin Pop
            (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
383 02da9d07 Iustin Pop
            "Save cluster state at the end of the processing to FILE"
384 02da9d07 Iustin Pop
385 df18fdfe Iustin Pop
oShowHelp :: OptType
386 df18fdfe Iustin Pop
oShowHelp = Option "h" ["help"]
387 df18fdfe Iustin Pop
            (NoArg (\ opts -> Ok opts { optShowHelp = True}))
388 df18fdfe Iustin Pop
            "show help"
389 df18fdfe Iustin Pop
390 df18fdfe Iustin Pop
oShowVer :: OptType
391 df18fdfe Iustin Pop
oShowVer = Option "V" ["version"]
392 df18fdfe Iustin Pop
           (NoArg (\ opts -> Ok opts { optShowVer = True}))
393 df18fdfe Iustin Pop
           "show the version of the program"
394 0f15cc76 Iustin Pop
395 294bb337 Iustin Pop
oStdSpec :: OptType
396 294bb337 Iustin Pop
oStdSpec = Option "" ["standard-alloc"]
397 294bb337 Iustin Pop
             (ReqArg (\ inp opts -> do
398 294bb337 Iustin Pop
                        tspec <- parseISpecString "standard" inp
399 be468da0 Iustin Pop
                        return $ opts { optStdSpec = Just tspec } )
400 294bb337 Iustin Pop
              "STDSPEC")
401 294bb337 Iustin Pop
             "enable standard specs allocation, given as 'disk,ram,cpu'"
402 294bb337 Iustin Pop
403 ee4ffc8a Iustin Pop
oTestCount :: OptType
404 ee4ffc8a Iustin Pop
oTestCount = Option "" ["test-count"]
405 ee4ffc8a Iustin Pop
             (ReqArg (\ inp opts -> do
406 ee4ffc8a Iustin Pop
                        tcount <- tryRead "parsing test count" inp
407 ee4ffc8a Iustin Pop
                        return $ opts { optTestCount = Just tcount } )
408 ee4ffc8a Iustin Pop
              "COUNT")
409 ee4ffc8a Iustin Pop
             "override the target test count"
410 ee4ffc8a Iustin Pop
411 1f9066c0 Iustin Pop
oTieredSpec :: OptType
412 1f9066c0 Iustin Pop
oTieredSpec = Option "" ["tiered-alloc"]
413 1f9066c0 Iustin Pop
             (ReqArg (\ inp opts -> do
414 7da760ca Iustin Pop
                        tspec <- parseISpecString "tiered" inp
415 cd08cfa4 Iustin Pop
                        return $ opts { optTieredSpec = Just tspec } )
416 1f9066c0 Iustin Pop
              "TSPEC")
417 7f4e37f0 Iustin Pop
             "enable tiered specs allocation, given as 'disk,ram,cpu'"
418 1f9066c0 Iustin Pop
419 509809db Iustin Pop
oReplay :: OptType
420 509809db Iustin Pop
oReplay = Option "" ["replay"]
421 509809db Iustin Pop
          (ReqArg (\ stat opts -> Ok opts { optReplay = Just stat } ) "STATE")
422 509809db Iustin Pop
          "Pre-seed the random number generator with STATE"
423 509809db Iustin Pop
424 df18fdfe Iustin Pop
oVerbose :: OptType
425 df18fdfe Iustin Pop
oVerbose = Option "v" ["verbose"]
426 df18fdfe Iustin Pop
           (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
427 df18fdfe Iustin Pop
           "increase the verbosity level"
428 fae371cc Iustin Pop
429 525bfb36 Iustin Pop
-- * Functions
430 525bfb36 Iustin Pop
431 519edd9f Iustin Pop
-- | Helper for parsing a yes\/no command line flag.
432 a7ea861a Iustin Pop
parseYesNo :: Bool         -- ^ Default value (when we get a @Nothing@)
433 519edd9f Iustin Pop
           -> Maybe String -- ^ Parameter value
434 519edd9f Iustin Pop
           -> Result Bool  -- ^ Resulting boolean value
435 519edd9f Iustin Pop
parseYesNo v Nothing      = return v
436 519edd9f Iustin Pop
parseYesNo _ (Just "yes") = return True
437 519edd9f Iustin Pop
parseYesNo _ (Just "no")  = return False
438 a7ea861a Iustin Pop
parseYesNo _ (Just s)     = fail ("Invalid choice '" ++ s ++
439 a7ea861a Iustin Pop
                                  "', pass one of 'yes' or 'no'")
440 519edd9f Iustin Pop
441 525bfb36 Iustin Pop
-- | Usage info.
442 0427285d Iustin Pop
usageHelp :: String -> [OptType] -> String
443 9f6dcdea Iustin Pop
usageHelp progname =
444 cd08cfa4 Iustin Pop
  usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
445 cd08cfa4 Iustin Pop
             progname Version.version progname)
446 78694255 Iustin Pop
447 51c3d88f Iustin Pop
-- | Show the program version info.
448 51c3d88f Iustin Pop
versionInfo :: String -> String
449 51c3d88f Iustin Pop
versionInfo progname =
450 51c3d88f Iustin Pop
  printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
451 51c3d88f Iustin Pop
         progname Version.version compilerName
452 51c3d88f Iustin Pop
         (Data.Version.showVersion compilerVersion)
453 51c3d88f Iustin Pop
         os arch
454 51c3d88f Iustin Pop
455 525bfb36 Iustin Pop
-- | Command line parser, using the 'Options' structure.
456 0427285d Iustin Pop
parseOpts :: [String]               -- ^ The command line arguments
457 0427285d Iustin Pop
          -> String                 -- ^ The program name
458 0427285d Iustin Pop
          -> [OptType]              -- ^ The supported command line options
459 0427285d Iustin Pop
          -> IO (Options, [String]) -- ^ The resulting options and leftover
460 0427285d Iustin Pop
                                    -- arguments
461 0427285d Iustin Pop
parseOpts argv progname options =
462 51c3d88f Iustin Pop
  case parseOptsInner argv progname options of
463 51c3d88f Iustin Pop
    Left (code, msg) -> do
464 51c3d88f Iustin Pop
      hPutStr (if code == 0 then stdout else stderr) msg
465 51c3d88f Iustin Pop
      exitWith (if code == 0 then ExitSuccess else ExitFailure code)
466 51c3d88f Iustin Pop
    Right result ->
467 51c3d88f Iustin Pop
      return result
468 51c3d88f Iustin Pop
469 51c3d88f Iustin Pop
-- | Inner parse options. The arguments are similar to 'parseOpts',
470 51c3d88f Iustin Pop
-- but it returns either a 'Left' composed of exit code and message,
471 51c3d88f Iustin Pop
-- or a 'Right' for the success case.
472 51c3d88f Iustin Pop
parseOptsInner :: [String] -> String -> [OptType]
473 51c3d88f Iustin Pop
               -> Either (Int, String) (Options, [String])
474 51c3d88f Iustin Pop
parseOptsInner argv progname options =
475 cd08cfa4 Iustin Pop
  case getOpt Permute options argv of
476 cd08cfa4 Iustin Pop
    (o, n, []) ->
477 51c3d88f Iustin Pop
      let (pr, args) = (foldM (flip id) defaultOptions o, n)
478 51c3d88f Iustin Pop
      in case pr of
479 51c3d88f Iustin Pop
           Bad msg -> Left (1, "Error while parsing command\
480 51c3d88f Iustin Pop
                               \line arguments:\n" ++ msg ++ "\n")
481 51c3d88f Iustin Pop
           Ok po ->
482 51c3d88f Iustin Pop
             select (Right (po, args))
483 51c3d88f Iustin Pop
                 [ (optShowHelp po, Left (0, usageHelp progname options))
484 51c3d88f Iustin Pop
                 , (optShowVer po,  Left (0, versionInfo progname))
485 51c3d88f Iustin Pop
                 ]
486 51c3d88f Iustin Pop
    (_, _, errs) ->
487 51c3d88f Iustin Pop
      Left (2, "Command line error: "  ++ concat errs ++ "\n" ++
488 51c3d88f Iustin Pop
            usageHelp progname options)
489 209b3711 Iustin Pop
490 9188aeef Iustin Pop
-- | A shell script template for autogenerated scripts.
491 e0eb63f0 Iustin Pop
shTemplate :: String
492 e0eb63f0 Iustin Pop
shTemplate =
493 cd08cfa4 Iustin Pop
  printf "#!/bin/sh\n\n\
494 cd08cfa4 Iustin Pop
         \# Auto-generated script for executing cluster rebalancing\n\n\
495 cd08cfa4 Iustin Pop
         \# To stop, touch the file /tmp/stop-htools\n\n\
496 cd08cfa4 Iustin Pop
         \set -e\n\n\
497 cd08cfa4 Iustin Pop
         \check() {\n\
498 cd08cfa4 Iustin Pop
         \  if [ -f /tmp/stop-htools ]; then\n\
499 cd08cfa4 Iustin Pop
         \    echo 'Stop requested, exiting'\n\
500 cd08cfa4 Iustin Pop
         \    exit 0\n\
501 cd08cfa4 Iustin Pop
         \  fi\n\
502 cd08cfa4 Iustin Pop
         \}\n\n"
503 417f6b50 Iustin Pop
504 417f6b50 Iustin Pop
-- | Optionally print the node list.
505 417f6b50 Iustin Pop
maybePrintNodes :: Maybe [String]       -- ^ The field list
506 417f6b50 Iustin Pop
                -> String               -- ^ Informational message
507 417f6b50 Iustin Pop
                -> ([String] -> String) -- ^ Function to generate the listing
508 417f6b50 Iustin Pop
                -> IO ()
509 417f6b50 Iustin Pop
maybePrintNodes Nothing _ _ = return ()
510 417f6b50 Iustin Pop
maybePrintNodes (Just fields) msg fn = do
511 417f6b50 Iustin Pop
  hPutStrLn stderr ""
512 417f6b50 Iustin Pop
  hPutStrLn stderr (msg ++ " status:")
513 417f6b50 Iustin Pop
  hPutStrLn stderr $ fn fields
514 33e44f0c Iustin Pop
515 33e44f0c Iustin Pop
516 33e44f0c Iustin Pop
-- | Optionally print the instance list.
517 33e44f0c Iustin Pop
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
518 33e44f0c Iustin Pop
                -> String -- ^ Type of the instance map (e.g. initial)
519 33e44f0c Iustin Pop
                -> String -- ^ The instance data
520 33e44f0c Iustin Pop
                -> IO ()
521 33e44f0c Iustin Pop
maybePrintInsts do_print msg instdata =
522 33e44f0c Iustin Pop
  when do_print $ do
523 33e44f0c Iustin Pop
    hPutStrLn stderr ""
524 33e44f0c Iustin Pop
    hPutStrLn stderr $ msg ++ " instance map:"
525 33e44f0c Iustin Pop
    hPutStr stderr instdata
526 8cd36391 Iustin Pop
527 8cd36391 Iustin Pop
-- | Function to display warning messages from parsing the cluster
528 8cd36391 Iustin Pop
-- state.
529 8cd36391 Iustin Pop
maybeShowWarnings :: [String] -- ^ The warning messages
530 8cd36391 Iustin Pop
                  -> IO ()
531 8cd36391 Iustin Pop
maybeShowWarnings fix_msgs =
532 8cd36391 Iustin Pop
  unless (null fix_msgs) $ do
533 8cd36391 Iustin Pop
    hPutStrLn stderr "Warning: cluster has inconsistent data:"
534 8cd36391 Iustin Pop
    hPutStrLn stderr . unlines . map (printf "  - %s") $ fix_msgs
535 5296ee23 Iustin Pop
536 284e9822 Iustin Pop
-- | Potentially set the node as offline based on passed offline list.
537 284e9822 Iustin Pop
setNodeOffline :: [Ndx] -> Node.Node -> Node.Node
538 284e9822 Iustin Pop
setNodeOffline offline_indices n =
539 284e9822 Iustin Pop
  if Node.idx n `elem` offline_indices
540 284e9822 Iustin Pop
    then Node.setOffline n True
541 284e9822 Iustin Pop
    else n
542 284e9822 Iustin Pop
543 5296ee23 Iustin Pop
-- | Set node properties based on command line options.
544 5296ee23 Iustin Pop
setNodeStatus :: Options -> Node.List -> IO Node.List
545 5296ee23 Iustin Pop
setNodeStatus opts fixed_nl = do
546 5296ee23 Iustin Pop
  let offline_passed = optOffline opts
547 5296ee23 Iustin Pop
      all_nodes = Container.elems fixed_nl
548 5296ee23 Iustin Pop
      offline_lkp = map (lookupName (map Node.name all_nodes)) offline_passed
549 5296ee23 Iustin Pop
      offline_wrong = filter (not . goodLookupResult) offline_lkp
550 5296ee23 Iustin Pop
      offline_names = map lrContent offline_lkp
551 5296ee23 Iustin Pop
      offline_indices = map Node.idx $
552 5296ee23 Iustin Pop
                        filter (\n -> Node.name n `elem` offline_names)
553 5296ee23 Iustin Pop
                               all_nodes
554 5296ee23 Iustin Pop
      m_cpu = optMcpu opts
555 5296ee23 Iustin Pop
      m_dsk = optMdsk opts
556 5296ee23 Iustin Pop
557 3603605a Iustin Pop
  unless (null offline_wrong) $ do
558 5296ee23 Iustin Pop
         hPrintf stderr "Error: Wrong node name(s) set as offline: %s\n"
559 5296ee23 Iustin Pop
                     (commaJoin (map lrContent offline_wrong)) :: IO ()
560 5296ee23 Iustin Pop
         exitWith $ ExitFailure 1
561 284e9822 Iustin Pop
  let setMCpuFn = case m_cpu of
562 284e9822 Iustin Pop
                    Nothing -> id
563 284e9822 Iustin Pop
                    Just new_mcpu -> flip Node.setMcpu new_mcpu
564 284e9822 Iustin Pop
  let nm = Container.map (setNodeOffline offline_indices .
565 284e9822 Iustin Pop
                          flip Node.setMdsk m_dsk .
566 284e9822 Iustin Pop
                          setMCpuFn) fixed_nl
567 284e9822 Iustin Pop
  return nm