Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ 88a10df5

History | View | Annotate | Download (21.6 kB)

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