Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / CLI.hs @ 28f19313

History | View | Annotate | Download (16.6 kB)

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