Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ 417cc253

History | View | Annotate | Download (21 kB)

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