Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ 3158250d

History | View | Annotate | Download (18 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 0427285d Iustin Pop
    ( Options(..)
32 0427285d Iustin Pop
    , OptType
33 75d1edf8 Iustin Pop
    , parseOpts
34 e0eb63f0 Iustin Pop
    , shTemplate
35 ba9349b8 Iustin Pop
    , defaultLuxiSocket
36 417f6b50 Iustin Pop
    , maybePrintNodes
37 33e44f0c Iustin Pop
    , maybePrintInsts
38 0427285d Iustin Pop
    -- * The options
39 16c2369c Iustin Pop
    , oDataFile
40 df18fdfe Iustin Pop
    , oDiskMoves
41 c4bb977b Iustin Pop
    , oDiskTemplate
42 df18fdfe Iustin Pop
    , oDynuFile
43 f0f21ec4 Iustin Pop
    , oEvacMode
44 10f396e1 Iustin Pop
    , oExInst
45 df18fdfe Iustin Pop
    , oExTags
46 0df5a1b4 Iustin Pop
    , oExecJobs
47 a423b510 Iustin Pop
    , oGroup
48 0427285d Iustin Pop
    , oIDisk
49 df18fdfe Iustin Pop
    , oIMem
50 df18fdfe Iustin Pop
    , oIVcpus
51 c4bb977b Iustin Pop
    , oInstMoves
52 df18fdfe Iustin Pop
    , oLuxiSocket
53 0427285d Iustin Pop
    , oMaxCpu
54 df18fdfe Iustin Pop
    , oMaxSolLength
55 0427285d Iustin Pop
    , oMinDisk
56 4f807a57 Iustin Pop
    , oMinGain
57 4f807a57 Iustin Pop
    , oMinGainLim
58 df18fdfe Iustin Pop
    , oMinScore
59 df18fdfe Iustin Pop
    , oNoHeaders
60 df18fdfe Iustin Pop
    , oNodeSim
61 df18fdfe Iustin Pop
    , oOfflineNode
62 df18fdfe Iustin Pop
    , oOneline
63 df18fdfe Iustin Pop
    , oOutputDir
64 df18fdfe Iustin Pop
    , oPrintCommands
65 df18fdfe Iustin Pop
    , oPrintInsts
66 df18fdfe Iustin Pop
    , oPrintNodes
67 df18fdfe Iustin Pop
    , oQuiet
68 df18fdfe Iustin Pop
    , oRapiMaster
69 509809db Iustin Pop
    , oReplay
70 02da9d07 Iustin Pop
    , oSaveCluster
71 c4bb977b Iustin Pop
    , oSelInst
72 0427285d Iustin Pop
    , oShowHelp
73 df18fdfe Iustin Pop
    , oShowVer
74 df18fdfe Iustin Pop
    , oTieredSpec
75 df18fdfe Iustin Pop
    , oVerbose
76 209b3711 Iustin Pop
    ) where
77 209b3711 Iustin Pop
78 cc532bdd Iustin Pop
import Control.Monad
79 e8f89bb6 Iustin Pop
import Data.Maybe (fromMaybe)
80 8e445e6d Iustin Pop
import qualified Data.Version
81 209b3711 Iustin Pop
import System.Console.GetOpt
82 209b3711 Iustin Pop
import System.IO
83 209b3711 Iustin Pop
import System.Info
84 209b3711 Iustin Pop
import System
85 e8f89bb6 Iustin Pop
import Text.Printf (printf)
86 209b3711 Iustin Pop
87 209b3711 Iustin Pop
import qualified Ganeti.HTools.Version as Version(version)
88 a69ff623 Iustin Pop
import qualified Ganeti.Constants as C
89 92e32d76 Iustin Pop
import Ganeti.HTools.Types
90 1f9066c0 Iustin Pop
import Ganeti.HTools.Utils
91 fae371cc Iustin Pop
92 525bfb36 Iustin Pop
-- * Constants
93 525bfb36 Iustin Pop
94 525bfb36 Iustin Pop
-- | The default value for the luxi socket.
95 525bfb36 Iustin Pop
--
96 525bfb36 Iustin Pop
-- This is re-exported from the "Ganeti.Constants" module.
97 8e445e6d Iustin Pop
defaultLuxiSocket :: FilePath
98 a69ff623 Iustin Pop
defaultLuxiSocket = C.masterSocket
99 8e445e6d Iustin Pop
100 525bfb36 Iustin Pop
-- * Data types
101 525bfb36 Iustin Pop
102 0427285d Iustin Pop
-- | Command line options structure.
103 0427285d Iustin Pop
data Options = Options
104 df18fdfe Iustin Pop
    { optDataFile    :: Maybe FilePath -- ^ Path to the cluster data file
105 df18fdfe Iustin Pop
    , optDiskMoves   :: Bool           -- ^ Allow disk moves
106 8fcfb767 Guido Trotter
    , optInstMoves   :: Bool           -- ^ Allow instance moves
107 c4bb977b Iustin Pop
    , optDiskTemplate :: DiskTemplate  -- ^ The requested disk template
108 df18fdfe Iustin Pop
    , optDynuFile    :: Maybe FilePath -- ^ Optional file with dynamic use data
109 f0f21ec4 Iustin Pop
    , optEvacMode    :: Bool           -- ^ Enable evacuation mode
110 10f396e1 Iustin Pop
    , optExInst      :: [String]       -- ^ Instances to be excluded
111 df18fdfe Iustin Pop
    , optExTags      :: Maybe [String] -- ^ Tags to use for exclusion
112 1f9066c0 Iustin Pop
    , optExecJobs    :: Bool           -- ^ Execute the commands via Luxi
113 a423b510 Iustin Pop
    , optGroup       :: Maybe GroupID  -- ^ The UUID of the group to process
114 ddef0585 Guido Trotter
    , optSelInst     :: [String]       -- ^ Instances to be excluded
115 1f9066c0 Iustin Pop
    , optISpec       :: RSpec          -- ^ Requested instance specs
116 df18fdfe Iustin Pop
    , optLuxi        :: Maybe FilePath -- ^ Collect data from Luxi
117 df18fdfe Iustin Pop
    , optMaster      :: String         -- ^ Collect data from RAPI
118 df18fdfe Iustin Pop
    , optMaxLength   :: Int            -- ^ Stop after this many steps
119 1f9066c0 Iustin Pop
    , optMcpu        :: Double         -- ^ Max cpu ratio for nodes
120 1f9066c0 Iustin Pop
    , optMdsk        :: Double         -- ^ Max disk usage ratio for nodes
121 4f807a57 Iustin Pop
    , optMinGain     :: Score          -- ^ Min gain we aim for in a step
122 4f807a57 Iustin Pop
    , optMinGainLim  :: Score          -- ^ Limit below which we apply mingain
123 df18fdfe Iustin Pop
    , optMinScore    :: Score          -- ^ The minimum score we aim for
124 df18fdfe Iustin Pop
    , optNoHeaders   :: Bool           -- ^ Do not show a header line
125 9983063b Iustin Pop
    , optNodeSim     :: [String]       -- ^ Cluster simulation mode
126 df18fdfe Iustin Pop
    , optOffline     :: [String]       -- ^ Names of offline nodes
127 df18fdfe Iustin Pop
    , optOneline     :: Bool           -- ^ Switch output to a single line
128 df18fdfe Iustin Pop
    , optOutPath     :: FilePath       -- ^ Path to the output directory
129 02da9d07 Iustin Pop
    , optSaveCluster :: Maybe FilePath -- ^ Save cluster state to this file
130 df18fdfe Iustin Pop
    , optShowCmds    :: Maybe FilePath -- ^ Whether to show the command list
131 1f9066c0 Iustin Pop
    , optShowHelp    :: Bool           -- ^ Just show the help
132 df18fdfe Iustin Pop
    , optShowInsts   :: Bool           -- ^ Whether to show the instance map
133 df18fdfe Iustin Pop
    , optShowNodes   :: Maybe [String] -- ^ Whether to show node status
134 df18fdfe Iustin Pop
    , optShowVer     :: Bool           -- ^ Just show the program version
135 df18fdfe Iustin Pop
    , optTieredSpec  :: Maybe RSpec    -- ^ Requested specs for tiered mode
136 509809db Iustin Pop
    , optReplay      :: Maybe String   -- ^ Unittests: RNG state
137 df18fdfe Iustin Pop
    , optVerbose     :: Int            -- ^ Verbosity level
138 0427285d Iustin Pop
    } deriving Show
139 0427285d Iustin Pop
140 0427285d Iustin Pop
-- | Default values for the command line options.
141 0427285d Iustin Pop
defaultOptions :: Options
142 0427285d Iustin Pop
defaultOptions  = Options
143 df18fdfe Iustin Pop
 { optDataFile    = Nothing
144 df18fdfe Iustin Pop
 , optDiskMoves   = True
145 8fcfb767 Guido Trotter
 , optInstMoves   = True
146 c4bb977b Iustin Pop
 , optDiskTemplate = DTDrbd8
147 df18fdfe Iustin Pop
 , optDynuFile    = Nothing
148 f0f21ec4 Iustin Pop
 , optEvacMode    = False
149 10f396e1 Iustin Pop
 , optExInst      = []
150 df18fdfe Iustin Pop
 , optExTags      = Nothing
151 1f9066c0 Iustin Pop
 , optExecJobs    = False
152 a423b510 Iustin Pop
 , optGroup       = Nothing
153 ddef0585 Guido Trotter
 , optSelInst     = []
154 1f9066c0 Iustin Pop
 , optISpec       = RSpec 1 4096 102400
155 df18fdfe Iustin Pop
 , optLuxi        = Nothing
156 df18fdfe Iustin Pop
 , optMaster      = ""
157 df18fdfe Iustin Pop
 , optMaxLength   = -1
158 f4c0b8c5 Iustin Pop
 , optMcpu        = defVcpuRatio
159 f4c0b8c5 Iustin Pop
 , optMdsk        = defReservedDiskRatio
160 4f807a57 Iustin Pop
 , optMinGain     = 1e-2
161 4f807a57 Iustin Pop
 , optMinGainLim  = 1e-1
162 df18fdfe Iustin Pop
 , optMinScore    = 1e-9
163 df18fdfe Iustin Pop
 , optNoHeaders   = False
164 9983063b Iustin Pop
 , optNodeSim     = []
165 df18fdfe Iustin Pop
 , optOffline     = []
166 df18fdfe Iustin Pop
 , optOneline     = False
167 df18fdfe Iustin Pop
 , optOutPath     = "."
168 02da9d07 Iustin Pop
 , optSaveCluster = Nothing
169 df18fdfe Iustin Pop
 , optShowCmds    = Nothing
170 1f9066c0 Iustin Pop
 , optShowHelp    = False
171 df18fdfe Iustin Pop
 , optShowInsts   = False
172 df18fdfe Iustin Pop
 , optShowNodes   = Nothing
173 df18fdfe Iustin Pop
 , optShowVer     = False
174 df18fdfe Iustin Pop
 , optTieredSpec  = Nothing
175 509809db Iustin Pop
 , optReplay      = Nothing
176 df18fdfe Iustin Pop
 , optVerbose     = 1
177 0427285d Iustin Pop
 }
178 0427285d Iustin Pop
179 525bfb36 Iustin Pop
-- | Abrreviation for the option type.
180 2f567ac0 Iustin Pop
type OptType = OptDescr (Options -> Result Options)
181 0427285d Iustin Pop
182 525bfb36 Iustin Pop
-- * Command line options
183 525bfb36 Iustin Pop
184 16c2369c Iustin Pop
oDataFile :: OptType
185 16c2369c Iustin Pop
oDataFile = Option "t" ["text-data"]
186 16c2369c Iustin Pop
            (ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
187 16c2369c Iustin Pop
            "the cluster data FILE"
188 0427285d Iustin Pop
189 df18fdfe Iustin Pop
oDiskMoves :: OptType
190 df18fdfe Iustin Pop
oDiskMoves = Option "" ["no-disk-moves"]
191 df18fdfe Iustin Pop
             (NoArg (\ opts -> Ok opts { optDiskMoves = False}))
192 df18fdfe Iustin Pop
             "disallow disk moves from the list of allowed instance changes,\
193 df18fdfe Iustin Pop
             \ thus allowing only the 'cheap' failover/migrate operations"
194 b2278348 Iustin Pop
195 c4bb977b Iustin Pop
oDiskTemplate :: OptType
196 c4bb977b Iustin Pop
oDiskTemplate = Option "" ["disk-template"]
197 c4bb977b Iustin Pop
                (ReqArg (\ t opts -> do
198 c4bb977b Iustin Pop
                           dt <- dtFromString t
199 c4bb977b Iustin Pop
                           return $ opts { optDiskTemplate = dt }) "TEMPLATE")
200 c4bb977b Iustin Pop
                "select the desired disk template"
201 c4bb977b Iustin Pop
202 ddef0585 Guido Trotter
oSelInst :: OptType
203 ddef0585 Guido Trotter
oSelInst = Option "" ["select-instances"]
204 ddef0585 Guido Trotter
          (ReqArg (\ f opts -> Ok opts { optSelInst = sepSplit ',' f }) "INSTS")
205 ddef0585 Guido Trotter
          "only select given instances for any moves"
206 ddef0585 Guido Trotter
207 8fcfb767 Guido Trotter
oInstMoves :: OptType
208 8fcfb767 Guido Trotter
oInstMoves = Option "" ["no-instance-moves"]
209 8fcfb767 Guido Trotter
             (NoArg (\ opts -> Ok opts { optInstMoves = False}))
210 8fcfb767 Guido Trotter
             "disallow instance (primary node) moves from the list of allowed,\
211 8fcfb767 Guido Trotter
             \ instance changes, thus allowing only slower, but sometimes\
212 8fcfb767 Guido Trotter
             \ safer, drbd secondary changes"
213 8fcfb767 Guido Trotter
214 df18fdfe Iustin Pop
oDynuFile :: OptType
215 df18fdfe Iustin Pop
oDynuFile = Option "U" ["dynu-file"]
216 df18fdfe Iustin Pop
            (ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
217 df18fdfe Iustin Pop
            "Import dynamic utilisation data from the given FILE"
218 0427285d Iustin Pop
219 f0f21ec4 Iustin Pop
oEvacMode :: OptType
220 f0f21ec4 Iustin Pop
oEvacMode = Option "E" ["evac-mode"]
221 f0f21ec4 Iustin Pop
            (NoArg (\opts -> Ok opts { optEvacMode = True }))
222 f0f21ec4 Iustin Pop
            "enable evacuation mode, where the algorithm only moves \
223 f0f21ec4 Iustin Pop
            \ instances away from offline and drained nodes"
224 f0f21ec4 Iustin Pop
225 10f396e1 Iustin Pop
oExInst :: OptType
226 10f396e1 Iustin Pop
oExInst = Option "" ["exclude-instances"]
227 10f396e1 Iustin Pop
          (ReqArg (\ f opts -> Ok opts { optExInst = sepSplit ',' f }) "INSTS")
228 6c30ce16 Guido Trotter
          "exclude given instances from any moves"
229 10f396e1 Iustin Pop
230 df18fdfe Iustin Pop
oExTags :: OptType
231 df18fdfe Iustin Pop
oExTags = Option "" ["exclusion-tags"]
232 df18fdfe Iustin Pop
            (ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
233 df18fdfe Iustin Pop
             "TAG,...") "Enable instance exclusion based on given tag prefix"
234 0427285d Iustin Pop
235 0df5a1b4 Iustin Pop
oExecJobs :: OptType
236 0df5a1b4 Iustin Pop
oExecJobs = Option "X" ["exec"]
237 2f567ac0 Iustin Pop
             (NoArg (\ opts -> Ok opts { optExecJobs = True}))
238 0df5a1b4 Iustin Pop
             "execute the suggested moves via Luxi (only available when using\
239 71e635f3 Renรฉ Nussbaumer
             \ it for data gathering)"
240 0df5a1b4 Iustin Pop
241 a423b510 Iustin Pop
oGroup :: OptType
242 a423b510 Iustin Pop
oGroup = Option "G" ["group"]
243 a423b510 Iustin Pop
            (ReqArg (\ f o -> Ok o { optGroup = Just f }) "ID")
244 a423b510 Iustin Pop
            "the ID of the group to balance"
245 a423b510 Iustin Pop
246 df18fdfe Iustin Pop
oIDisk :: OptType
247 df18fdfe Iustin Pop
oIDisk = Option "" ["disk"]
248 247f77b7 Iustin Pop
         (ReqArg (\ d opts -> do
249 247f77b7 Iustin Pop
                    dsk <- annotateResult ("--disk option") (parseUnit d)
250 247f77b7 Iustin Pop
                    let ospec = optISpec opts
251 247f77b7 Iustin Pop
                        nspec = ospec { rspecDsk = dsk }
252 247f77b7 Iustin Pop
                    return $ opts { optISpec = nspec }) "DISK")
253 df18fdfe Iustin Pop
         "disk size for instances"
254 0427285d Iustin Pop
255 0427285d Iustin Pop
oIMem :: OptType
256 0427285d Iustin Pop
oIMem = Option "" ["memory"]
257 247f77b7 Iustin Pop
        (ReqArg (\ m opts -> do
258 247f77b7 Iustin Pop
                   mem <- annotateResult ("--memory option") (parseUnit m)
259 247f77b7 Iustin Pop
                   let ospec = optISpec opts
260 247f77b7 Iustin Pop
                       nspec = ospec { rspecMem = mem }
261 247f77b7 Iustin Pop
                   return $ opts { optISpec = nspec }) "MEMORY")
262 0427285d Iustin Pop
        "memory size for instances"
263 0427285d Iustin Pop
264 0427285d Iustin Pop
oIVcpus :: OptType
265 0427285d Iustin Pop
oIVcpus = Option "" ["vcpus"]
266 247f77b7 Iustin Pop
          (ReqArg (\ p opts -> do
267 247f77b7 Iustin Pop
                     vcpus <- tryRead "--vcpus option" p
268 247f77b7 Iustin Pop
                     let ospec = optISpec opts
269 247f77b7 Iustin Pop
                         nspec = ospec { rspecCpu = vcpus }
270 247f77b7 Iustin Pop
                     return $ opts { optISpec = nspec }) "NUM")
271 0427285d Iustin Pop
          "number of virtual cpus for instances"
272 0427285d Iustin Pop
273 df18fdfe Iustin Pop
oLuxiSocket :: OptType
274 df18fdfe Iustin Pop
oLuxiSocket = Option "L" ["luxi"]
275 df18fdfe Iustin Pop
              (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
276 df18fdfe Iustin Pop
                       fromMaybe defaultLuxiSocket) "SOCKET")
277 df18fdfe Iustin Pop
              "collect data via Luxi, optionally using the given SOCKET path"
278 0427285d Iustin Pop
279 0427285d Iustin Pop
oMaxCpu :: OptType
280 0427285d Iustin Pop
oMaxCpu = Option "" ["max-cpu"]
281 2f567ac0 Iustin Pop
          (ReqArg (\ n opts -> Ok opts { optMcpu = read n }) "RATIO")
282 f4c0b8c5 Iustin Pop
          "maximum virtual-to-physical cpu ratio for nodes (from 1\
283 f4c0b8c5 Iustin Pop
          \ upwards) [64]"
284 0427285d Iustin Pop
285 df18fdfe Iustin Pop
oMaxSolLength :: OptType
286 df18fdfe Iustin Pop
oMaxSolLength = Option "l" ["max-length"]
287 df18fdfe Iustin Pop
                (ReqArg (\ i opts -> Ok opts { optMaxLength = read i }) "N")
288 df18fdfe Iustin Pop
                "cap the solution at this many moves (useful for very\
289 df18fdfe Iustin Pop
                \ unbalanced clusters)"
290 df18fdfe Iustin Pop
291 0427285d Iustin Pop
oMinDisk :: OptType
292 0427285d Iustin Pop
oMinDisk = Option "" ["min-disk"]
293 2f567ac0 Iustin Pop
           (ReqArg (\ n opts -> Ok opts { optMdsk = read n }) "RATIO")
294 f4c0b8c5 Iustin Pop
           "minimum free disk space for nodes (between 0 and 1) [0]"
295 0427285d Iustin Pop
296 4f807a57 Iustin Pop
oMinGain :: OptType
297 4f807a57 Iustin Pop
oMinGain = Option "g" ["min-gain"]
298 4f807a57 Iustin Pop
            (ReqArg (\ g opts -> Ok opts { optMinGain = read g }) "DELTA")
299 4f807a57 Iustin Pop
            "minimum gain to aim for in a balancing step before giving up"
300 4f807a57 Iustin Pop
301 4f807a57 Iustin Pop
oMinGainLim :: OptType
302 4f807a57 Iustin Pop
oMinGainLim = Option "" ["min-gain-limit"]
303 4f807a57 Iustin Pop
            (ReqArg (\ g opts -> Ok opts { optMinGainLim = read g }) "SCORE")
304 4f807a57 Iustin Pop
            "minimum cluster score for which we start checking the min-gain"
305 4f807a57 Iustin Pop
306 df18fdfe Iustin Pop
oMinScore :: OptType
307 df18fdfe Iustin Pop
oMinScore = Option "e" ["min-score"]
308 df18fdfe Iustin Pop
            (ReqArg (\ e opts -> Ok opts { optMinScore = read e }) "EPSILON")
309 4f807a57 Iustin Pop
            "mininum score to aim for"
310 c0501c69 Iustin Pop
311 df18fdfe Iustin Pop
oNoHeaders :: OptType
312 df18fdfe Iustin Pop
oNoHeaders = Option "" ["no-headers"]
313 df18fdfe Iustin Pop
             (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
314 df18fdfe Iustin Pop
             "do not show a header line"
315 4f83a560 Iustin Pop
316 df18fdfe Iustin Pop
oNodeSim :: OptType
317 df18fdfe Iustin Pop
oNodeSim = Option "" ["simulate"]
318 9983063b Iustin Pop
            (ReqArg (\ f o -> Ok o { optNodeSim = f:optNodeSim o }) "SPEC")
319 df18fdfe Iustin Pop
            "simulate an empty cluster, given as 'num_nodes,disk,ram,cpu'"
320 df18fdfe Iustin Pop
321 df18fdfe Iustin Pop
oOfflineNode :: OptType
322 df18fdfe Iustin Pop
oOfflineNode = Option "O" ["offline"]
323 df18fdfe Iustin Pop
               (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
324 df18fdfe Iustin Pop
               "set node as offline"
325 df18fdfe Iustin Pop
326 df18fdfe Iustin Pop
oOneline :: OptType
327 df18fdfe Iustin Pop
oOneline = Option "o" ["oneline"]
328 df18fdfe Iustin Pop
           (NoArg (\ opts -> Ok opts { optOneline = True }))
329 df18fdfe Iustin Pop
           "print the ganeti command list for reaching the solution"
330 df18fdfe Iustin Pop
331 df18fdfe Iustin Pop
oOutputDir :: OptType
332 df18fdfe Iustin Pop
oOutputDir = Option "d" ["output-dir"]
333 df18fdfe Iustin Pop
             (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
334 df18fdfe Iustin Pop
             "directory in which to write output files"
335 df18fdfe Iustin Pop
336 df18fdfe Iustin Pop
oPrintCommands :: OptType
337 df18fdfe Iustin Pop
oPrintCommands = Option "C" ["print-commands"]
338 df18fdfe Iustin Pop
                 (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
339 df18fdfe Iustin Pop
                          fromMaybe "-")
340 df18fdfe Iustin Pop
                  "FILE")
341 df18fdfe Iustin Pop
                 "print the ganeti command list for reaching the solution,\
342 df18fdfe Iustin Pop
                 \ if an argument is passed then write the commands to a\
343 df18fdfe Iustin Pop
                 \ file named as such"
344 df18fdfe Iustin Pop
345 df18fdfe Iustin Pop
oPrintInsts :: OptType
346 df18fdfe Iustin Pop
oPrintInsts = Option "" ["print-instances"]
347 df18fdfe Iustin Pop
              (NoArg (\ opts -> Ok opts { optShowInsts = True }))
348 df18fdfe Iustin Pop
              "print the final instance map"
349 df18fdfe Iustin Pop
350 df18fdfe Iustin Pop
oPrintNodes :: OptType
351 df18fdfe Iustin Pop
oPrintNodes = Option "p" ["print-nodes"]
352 df18fdfe Iustin Pop
              (OptArg ((\ f opts ->
353 6dfa04fd Iustin Pop
                            let (prefix, realf) = case f of
354 6dfa04fd Iustin Pop
                                  '+':rest -> (["+"], rest)
355 6dfa04fd Iustin Pop
                                  _ -> ([], f)
356 6dfa04fd Iustin Pop
                                splitted = prefix ++ sepSplit ',' realf
357 df18fdfe Iustin Pop
                            in Ok opts { optShowNodes = Just splitted }) .
358 df18fdfe Iustin Pop
                       fromMaybe []) "FIELDS")
359 df18fdfe Iustin Pop
              "print the final node list"
360 df18fdfe Iustin Pop
361 df18fdfe Iustin Pop
oQuiet :: OptType
362 df18fdfe Iustin Pop
oQuiet = Option "q" ["quiet"]
363 df18fdfe Iustin Pop
         (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
364 df18fdfe Iustin Pop
         "decrease the verbosity level"
365 df18fdfe Iustin Pop
366 df18fdfe Iustin Pop
oRapiMaster :: OptType
367 df18fdfe Iustin Pop
oRapiMaster = Option "m" ["master"]
368 df18fdfe Iustin Pop
              (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
369 df18fdfe Iustin Pop
              "collect data via RAPI at the given ADDRESS"
370 df18fdfe Iustin Pop
371 02da9d07 Iustin Pop
oSaveCluster :: OptType
372 02da9d07 Iustin Pop
oSaveCluster = Option "S" ["save"]
373 02da9d07 Iustin Pop
            (ReqArg (\ f opts -> Ok opts { optSaveCluster = Just f }) "FILE")
374 02da9d07 Iustin Pop
            "Save cluster state at the end of the processing to FILE"
375 02da9d07 Iustin Pop
376 df18fdfe Iustin Pop
oShowHelp :: OptType
377 df18fdfe Iustin Pop
oShowHelp = Option "h" ["help"]
378 df18fdfe Iustin Pop
            (NoArg (\ opts -> Ok opts { optShowHelp = True}))
379 df18fdfe Iustin Pop
            "show help"
380 df18fdfe Iustin Pop
381 df18fdfe Iustin Pop
oShowVer :: OptType
382 df18fdfe Iustin Pop
oShowVer = Option "V" ["version"]
383 df18fdfe Iustin Pop
           (NoArg (\ opts -> Ok opts { optShowVer = True}))
384 df18fdfe Iustin Pop
           "show the version of the program"
385 0f15cc76 Iustin Pop
386 1f9066c0 Iustin Pop
oTieredSpec :: OptType
387 1f9066c0 Iustin Pop
oTieredSpec = Option "" ["tiered-alloc"]
388 1f9066c0 Iustin Pop
             (ReqArg (\ inp opts -> do
389 1f9066c0 Iustin Pop
                          let sp = sepSplit ',' inp
390 247f77b7 Iustin Pop
                          prs <- mapM (\(fn, val) -> fn val) $
391 247f77b7 Iustin Pop
                                 zip [ annotateResult "tiered specs memory" .
392 247f77b7 Iustin Pop
                                       parseUnit
393 247f77b7 Iustin Pop
                                     , annotateResult "tiered specs disk" .
394 247f77b7 Iustin Pop
                                       parseUnit
395 247f77b7 Iustin Pop
                                     , tryRead "tiered specs cpus"
396 247f77b7 Iustin Pop
                                     ] sp
397 1f9066c0 Iustin Pop
                          tspec <-
398 1f9066c0 Iustin Pop
                              case prs of
399 7f4e37f0 Iustin Pop
                                [dsk, ram, cpu] -> return $ RSpec cpu ram dsk
400 03c6d8fa Iustin Pop
                                _ -> Bad $ "Invalid specification: " ++ inp ++
401 03c6d8fa Iustin Pop
                                     ", expected disk,ram,cpu"
402 1f9066c0 Iustin Pop
                          return $ opts { optTieredSpec = Just tspec } )
403 1f9066c0 Iustin Pop
              "TSPEC")
404 7f4e37f0 Iustin Pop
             "enable tiered specs allocation, given as 'disk,ram,cpu'"
405 1f9066c0 Iustin Pop
406 509809db Iustin Pop
oReplay :: OptType
407 509809db Iustin Pop
oReplay = Option "" ["replay"]
408 509809db Iustin Pop
          (ReqArg (\ stat opts -> Ok opts { optReplay = Just stat } ) "STATE")
409 509809db Iustin Pop
          "Pre-seed the random number generator with STATE"
410 509809db Iustin Pop
411 df18fdfe Iustin Pop
oVerbose :: OptType
412 df18fdfe Iustin Pop
oVerbose = Option "v" ["verbose"]
413 df18fdfe Iustin Pop
           (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
414 df18fdfe Iustin Pop
           "increase the verbosity level"
415 fae371cc Iustin Pop
416 525bfb36 Iustin Pop
-- * Functions
417 525bfb36 Iustin Pop
418 525bfb36 Iustin Pop
-- | Usage info.
419 0427285d Iustin Pop
usageHelp :: String -> [OptType] -> String
420 9f6dcdea Iustin Pop
usageHelp progname =
421 78694255 Iustin Pop
    usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
422 9f6dcdea Iustin Pop
               progname Version.version progname)
423 78694255 Iustin Pop
424 525bfb36 Iustin Pop
-- | Command line parser, using the 'Options' structure.
425 0427285d Iustin Pop
parseOpts :: [String]               -- ^ The command line arguments
426 0427285d Iustin Pop
          -> String                 -- ^ The program name
427 0427285d Iustin Pop
          -> [OptType]              -- ^ The supported command line options
428 0427285d Iustin Pop
          -> IO (Options, [String]) -- ^ The resulting options and leftover
429 0427285d Iustin Pop
                                    -- arguments
430 0427285d Iustin Pop
parseOpts argv progname options =
431 209b3711 Iustin Pop
    case getOpt Permute options argv of
432 209b3711 Iustin Pop
      (o, n, []) ->
433 209b3711 Iustin Pop
          do
434 2f567ac0 Iustin Pop
            let (pr, args) = (foldM (flip id) defaultOptions o, n)
435 2f567ac0 Iustin Pop
            po <- (case pr of
436 2f567ac0 Iustin Pop
                     Bad msg -> do
437 2f567ac0 Iustin Pop
                       hPutStrLn stderr "Error while parsing command\
438 2f567ac0 Iustin Pop
                                        \line arguments:"
439 2f567ac0 Iustin Pop
                       hPutStrLn stderr msg
440 2f567ac0 Iustin Pop
                       exitWith $ ExitFailure 1
441 2f567ac0 Iustin Pop
                     Ok val -> return val)
442 0427285d Iustin Pop
            when (optShowHelp po) $ do
443 78694255 Iustin Pop
              putStr $ usageHelp progname options
444 209b3711 Iustin Pop
              exitWith ExitSuccess
445 0427285d Iustin Pop
            when (optShowVer po) $ do
446 75d1edf8 Iustin Pop
              printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
447 75d1edf8 Iustin Pop
                     progname Version.version
448 75d1edf8 Iustin Pop
                     compilerName (Data.Version.showVersion compilerVersion)
449 c939b58e Iustin Pop
                     os arch :: IO ()
450 75d1edf8 Iustin Pop
              exitWith ExitSuccess
451 2f567ac0 Iustin Pop
            return (po, args)
452 f723de38 Iustin Pop
      (_, _, errs) -> do
453 f723de38 Iustin Pop
        hPutStrLn stderr $ "Command line error: "  ++ concat errs
454 f723de38 Iustin Pop
        hPutStrLn stderr $ usageHelp progname options
455 f723de38 Iustin Pop
        exitWith $ ExitFailure 2
456 209b3711 Iustin Pop
457 9188aeef Iustin Pop
-- | A shell script template for autogenerated scripts.
458 e0eb63f0 Iustin Pop
shTemplate :: String
459 e0eb63f0 Iustin Pop
shTemplate =
460 e0eb63f0 Iustin Pop
    printf "#!/bin/sh\n\n\
461 e0eb63f0 Iustin Pop
           \# Auto-generated script for executing cluster rebalancing\n\n\
462 e0eb63f0 Iustin Pop
           \# To stop, touch the file /tmp/stop-htools\n\n\
463 e0eb63f0 Iustin Pop
           \set -e\n\n\
464 e0eb63f0 Iustin Pop
           \check() {\n\
465 e0eb63f0 Iustin Pop
           \  if [ -f /tmp/stop-htools ]; then\n\
466 e0eb63f0 Iustin Pop
           \    echo 'Stop requested, exiting'\n\
467 e0eb63f0 Iustin Pop
           \    exit 0\n\
468 e0eb63f0 Iustin Pop
           \  fi\n\
469 e0eb63f0 Iustin Pop
           \}\n\n"
470 417f6b50 Iustin Pop
471 417f6b50 Iustin Pop
-- | Optionally print the node list.
472 417f6b50 Iustin Pop
maybePrintNodes :: Maybe [String]       -- ^ The field list
473 417f6b50 Iustin Pop
                -> String               -- ^ Informational message
474 417f6b50 Iustin Pop
                -> ([String] -> String) -- ^ Function to generate the listing
475 417f6b50 Iustin Pop
                -> IO ()
476 417f6b50 Iustin Pop
maybePrintNodes Nothing _ _ = return ()
477 417f6b50 Iustin Pop
maybePrintNodes (Just fields) msg fn = do
478 417f6b50 Iustin Pop
  hPutStrLn stderr ""
479 417f6b50 Iustin Pop
  hPutStrLn stderr (msg ++ " status:")
480 417f6b50 Iustin Pop
  hPutStrLn stderr $ fn fields
481 33e44f0c Iustin Pop
482 33e44f0c Iustin Pop
483 33e44f0c Iustin Pop
-- | Optionally print the instance list.
484 33e44f0c Iustin Pop
maybePrintInsts :: Bool   -- ^ Whether to print the instance list
485 33e44f0c Iustin Pop
                -> String -- ^ Type of the instance map (e.g. initial)
486 33e44f0c Iustin Pop
                -> String -- ^ The instance data
487 33e44f0c Iustin Pop
                -> IO ()
488 33e44f0c Iustin Pop
maybePrintInsts do_print msg instdata =
489 33e44f0c Iustin Pop
  when do_print $ do
490 33e44f0c Iustin Pop
    hPutStrLn stderr ""
491 33e44f0c Iustin Pop
    hPutStrLn stderr $ msg ++ " instance map:"
492 33e44f0c Iustin Pop
    hPutStr stderr instdata