Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ 7da760ca

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