Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ 51c3d88f

History | View | Annotate | Download (19.8 kB)

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