Statistics
| Branch: | Tag: | Revision:

root / Ganeti / HTools / CLI.hs @ df18fdfe

History | View | Annotate | Download (13 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 e2fa2baf Iustin Pop
Copyright (C) 2009 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 0427285d Iustin Pop
    -- * The options
36 16c2369c Iustin Pop
    , oDataFile
37 df18fdfe Iustin Pop
    , oDiskMoves
38 df18fdfe Iustin Pop
    , oDynuFile
39 df18fdfe Iustin Pop
    , oExTags
40 0df5a1b4 Iustin Pop
    , oExecJobs
41 0427285d Iustin Pop
    , oIDisk
42 df18fdfe Iustin Pop
    , oIMem
43 0427285d Iustin Pop
    , oINodes
44 df18fdfe Iustin Pop
    , oIVcpus
45 df18fdfe Iustin Pop
    , oLuxiSocket
46 0427285d Iustin Pop
    , oMaxCpu
47 df18fdfe Iustin Pop
    , oMaxSolLength
48 0427285d Iustin Pop
    , oMinDisk
49 df18fdfe Iustin Pop
    , oMinScore
50 df18fdfe Iustin Pop
    , oNoHeaders
51 df18fdfe Iustin Pop
    , oNodeSim
52 df18fdfe Iustin Pop
    , oOfflineNode
53 df18fdfe Iustin Pop
    , oOneline
54 df18fdfe Iustin Pop
    , oOutputDir
55 df18fdfe Iustin Pop
    , oPrintCommands
56 df18fdfe Iustin Pop
    , oPrintInsts
57 df18fdfe Iustin Pop
    , oPrintNodes
58 df18fdfe Iustin Pop
    , oQuiet
59 df18fdfe Iustin Pop
    , oRapiMaster
60 0427285d Iustin Pop
    , oShowHelp
61 df18fdfe Iustin Pop
    , oShowVer
62 df18fdfe Iustin Pop
    , oTieredSpec
63 df18fdfe Iustin Pop
    , oVerbose
64 209b3711 Iustin Pop
    ) where
65 209b3711 Iustin Pop
66 e8f89bb6 Iustin Pop
import Data.Maybe (fromMaybe)
67 8e445e6d Iustin Pop
import qualified Data.Version
68 8e445e6d Iustin Pop
import Monad
69 209b3711 Iustin Pop
import System.Console.GetOpt
70 209b3711 Iustin Pop
import System.IO
71 209b3711 Iustin Pop
import System.Info
72 209b3711 Iustin Pop
import System
73 e8f89bb6 Iustin Pop
import Text.Printf (printf)
74 209b3711 Iustin Pop
75 209b3711 Iustin Pop
import qualified Ganeti.HTools.Version as Version(version)
76 92e32d76 Iustin Pop
import Ganeti.HTools.Types
77 1f9066c0 Iustin Pop
import Ganeti.HTools.Utils
78 fae371cc Iustin Pop
79 8e445e6d Iustin Pop
-- | The default value for the luxi socket
80 8e445e6d Iustin Pop
defaultLuxiSocket :: FilePath
81 8e445e6d Iustin Pop
defaultLuxiSocket = "/var/run/ganeti/socket/ganeti-master"
82 8e445e6d Iustin Pop
83 0427285d Iustin Pop
-- | Command line options structure.
84 0427285d Iustin Pop
data Options = Options
85 df18fdfe Iustin Pop
    { optDataFile    :: Maybe FilePath -- ^ Path to the cluster data file
86 df18fdfe Iustin Pop
    , optDiskMoves   :: Bool           -- ^ Allow disk moves
87 df18fdfe Iustin Pop
    , optDynuFile    :: Maybe FilePath -- ^ Optional file with dynamic use data
88 df18fdfe Iustin Pop
    , optExTags      :: Maybe [String] -- ^ Tags to use for exclusion
89 1f9066c0 Iustin Pop
    , optExecJobs    :: Bool           -- ^ Execute the commands via Luxi
90 1f9066c0 Iustin Pop
    , optINodes      :: Int            -- ^ Nodes required for an instance
91 1f9066c0 Iustin Pop
    , optISpec       :: RSpec          -- ^ Requested instance specs
92 df18fdfe Iustin Pop
    , optLuxi        :: Maybe FilePath -- ^ Collect data from Luxi
93 df18fdfe Iustin Pop
    , optMaster      :: String         -- ^ Collect data from RAPI
94 df18fdfe Iustin Pop
    , optMaxLength   :: Int            -- ^ Stop after this many steps
95 1f9066c0 Iustin Pop
    , optMcpu        :: Double         -- ^ Max cpu ratio for nodes
96 1f9066c0 Iustin Pop
    , optMdsk        :: Double         -- ^ Max disk usage ratio for nodes
97 df18fdfe Iustin Pop
    , optMinScore    :: Score          -- ^ The minimum score we aim for
98 df18fdfe Iustin Pop
    , optNoHeaders   :: Bool           -- ^ Do not show a header line
99 df18fdfe Iustin Pop
    , optNodeSim     :: Maybe String   -- ^ Cluster simulation mode
100 df18fdfe Iustin Pop
    , optOffline     :: [String]       -- ^ Names of offline nodes
101 df18fdfe Iustin Pop
    , optOneline     :: Bool           -- ^ Switch output to a single line
102 df18fdfe Iustin Pop
    , optOutPath     :: FilePath       -- ^ Path to the output directory
103 df18fdfe Iustin Pop
    , optShowCmds    :: Maybe FilePath -- ^ Whether to show the command list
104 1f9066c0 Iustin Pop
    , optShowHelp    :: Bool           -- ^ Just show the help
105 df18fdfe Iustin Pop
    , optShowInsts   :: Bool           -- ^ Whether to show the instance map
106 df18fdfe Iustin Pop
    , optShowNodes   :: Maybe [String] -- ^ Whether to show node status
107 df18fdfe Iustin Pop
    , optShowVer     :: Bool           -- ^ Just show the program version
108 df18fdfe Iustin Pop
    , optTieredSpec  :: Maybe RSpec    -- ^ Requested specs for tiered mode
109 df18fdfe Iustin Pop
    , optVerbose     :: Int            -- ^ Verbosity level
110 0427285d Iustin Pop
    } deriving Show
111 0427285d Iustin Pop
112 0427285d Iustin Pop
-- | Default values for the command line options.
113 0427285d Iustin Pop
defaultOptions :: Options
114 0427285d Iustin Pop
defaultOptions  = Options
115 df18fdfe Iustin Pop
 { optDataFile    = Nothing
116 df18fdfe Iustin Pop
 , optDiskMoves   = True
117 df18fdfe Iustin Pop
 , optDynuFile    = Nothing
118 df18fdfe Iustin Pop
 , optExTags      = Nothing
119 1f9066c0 Iustin Pop
 , optExecJobs    = False
120 1f9066c0 Iustin Pop
 , optINodes      = 2
121 1f9066c0 Iustin Pop
 , optISpec       = RSpec 1 4096 102400
122 df18fdfe Iustin Pop
 , optLuxi        = Nothing
123 df18fdfe Iustin Pop
 , optMaster      = ""
124 df18fdfe Iustin Pop
 , optMaxLength   = -1
125 1f9066c0 Iustin Pop
 , optMcpu        = -1
126 1f9066c0 Iustin Pop
 , optMdsk        = -1
127 df18fdfe Iustin Pop
 , optMinScore    = 1e-9
128 df18fdfe Iustin Pop
 , optNoHeaders   = False
129 df18fdfe Iustin Pop
 , optNodeSim     = Nothing
130 df18fdfe Iustin Pop
 , optOffline     = []
131 df18fdfe Iustin Pop
 , optOneline     = False
132 df18fdfe Iustin Pop
 , optOutPath     = "."
133 df18fdfe Iustin Pop
 , optShowCmds    = Nothing
134 1f9066c0 Iustin Pop
 , optShowHelp    = False
135 df18fdfe Iustin Pop
 , optShowInsts   = False
136 df18fdfe Iustin Pop
 , optShowNodes   = Nothing
137 df18fdfe Iustin Pop
 , optShowVer     = False
138 df18fdfe Iustin Pop
 , optTieredSpec  = Nothing
139 df18fdfe Iustin Pop
 , optVerbose     = 1
140 0427285d Iustin Pop
 }
141 0427285d Iustin Pop
142 0427285d Iustin Pop
-- | Abrreviation for the option type
143 2f567ac0 Iustin Pop
type OptType = OptDescr (Options -> Result Options)
144 0427285d Iustin Pop
145 16c2369c Iustin Pop
oDataFile :: OptType
146 16c2369c Iustin Pop
oDataFile = Option "t" ["text-data"]
147 16c2369c Iustin Pop
            (ReqArg (\ f o -> Ok o { optDataFile = Just f }) "FILE")
148 16c2369c Iustin Pop
            "the cluster data FILE"
149 0427285d Iustin Pop
150 df18fdfe Iustin Pop
oDiskMoves :: OptType
151 df18fdfe Iustin Pop
oDiskMoves = Option "" ["no-disk-moves"]
152 df18fdfe Iustin Pop
             (NoArg (\ opts -> Ok opts { optDiskMoves = False}))
153 df18fdfe Iustin Pop
             "disallow disk moves from the list of allowed instance changes,\
154 df18fdfe Iustin Pop
             \ thus allowing only the 'cheap' failover/migrate operations"
155 b2278348 Iustin Pop
156 df18fdfe Iustin Pop
oDynuFile :: OptType
157 df18fdfe Iustin Pop
oDynuFile = Option "U" ["dynu-file"]
158 df18fdfe Iustin Pop
            (ReqArg (\ f opts -> Ok opts { optDynuFile = Just f }) "FILE")
159 df18fdfe Iustin Pop
            "Import dynamic utilisation data from the given FILE"
160 0427285d Iustin Pop
161 df18fdfe Iustin Pop
oExTags :: OptType
162 df18fdfe Iustin Pop
oExTags = Option "" ["exclusion-tags"]
163 df18fdfe Iustin Pop
            (ReqArg (\ f opts -> Ok opts { optExTags = Just $ sepSplit ',' f })
164 df18fdfe Iustin Pop
             "TAG,...") "Enable instance exclusion based on given tag prefix"
165 0427285d Iustin Pop
166 0df5a1b4 Iustin Pop
oExecJobs :: OptType
167 0df5a1b4 Iustin Pop
oExecJobs = Option "X" ["exec"]
168 2f567ac0 Iustin Pop
             (NoArg (\ opts -> Ok opts { optExecJobs = True}))
169 0df5a1b4 Iustin Pop
             "execute the suggested moves via Luxi (only available when using\
170 71e635f3 Renรฉ Nussbaumer
             \ it for data gathering)"
171 0df5a1b4 Iustin Pop
172 df18fdfe Iustin Pop
oIDisk :: OptType
173 df18fdfe Iustin Pop
oIDisk = Option "" ["disk"]
174 df18fdfe Iustin Pop
         (ReqArg (\ d opts ->
175 df18fdfe Iustin Pop
                     let ospec = optISpec opts
176 df18fdfe Iustin Pop
                         nspec = ospec { rspecDsk = read d }
177 df18fdfe Iustin Pop
                     in Ok opts { optISpec = nspec }) "DISK")
178 df18fdfe Iustin Pop
         "disk size for instances"
179 0427285d Iustin Pop
180 0427285d Iustin Pop
oIMem :: OptType
181 0427285d Iustin Pop
oIMem = Option "" ["memory"]
182 1f9066c0 Iustin Pop
        (ReqArg (\ m opts ->
183 1f9066c0 Iustin Pop
                     let ospec = optISpec opts
184 1f9066c0 Iustin Pop
                         nspec = ospec { rspecMem = read m }
185 1f9066c0 Iustin Pop
                     in Ok opts { optISpec = nspec }) "MEMORY")
186 0427285d Iustin Pop
        "memory size for instances"
187 0427285d Iustin Pop
188 df18fdfe Iustin Pop
oINodes :: OptType
189 df18fdfe Iustin Pop
oINodes = Option "" ["req-nodes"]
190 df18fdfe Iustin Pop
          (ReqArg (\ n opts -> Ok opts { optINodes = read n }) "NODES")
191 df18fdfe Iustin Pop
          "number of nodes for the new instances (1=plain, 2=mirrored)"
192 0427285d Iustin Pop
193 0427285d Iustin Pop
oIVcpus :: OptType
194 0427285d Iustin Pop
oIVcpus = Option "" ["vcpus"]
195 1f9066c0 Iustin Pop
          (ReqArg (\ p opts ->
196 1f9066c0 Iustin Pop
                       let ospec = optISpec opts
197 1f9066c0 Iustin Pop
                           nspec = ospec { rspecCpu = read p }
198 1f9066c0 Iustin Pop
                       in Ok opts { optISpec = nspec }) "NUM")
199 0427285d Iustin Pop
          "number of virtual cpus for instances"
200 0427285d Iustin Pop
201 df18fdfe Iustin Pop
oLuxiSocket :: OptType
202 df18fdfe Iustin Pop
oLuxiSocket = Option "L" ["luxi"]
203 df18fdfe Iustin Pop
              (OptArg ((\ f opts -> Ok opts { optLuxi = Just f }) .
204 df18fdfe Iustin Pop
                       fromMaybe defaultLuxiSocket) "SOCKET")
205 df18fdfe Iustin Pop
              "collect data via Luxi, optionally using the given SOCKET path"
206 0427285d Iustin Pop
207 0427285d Iustin Pop
oMaxCpu :: OptType
208 0427285d Iustin Pop
oMaxCpu = Option "" ["max-cpu"]
209 2f567ac0 Iustin Pop
          (ReqArg (\ n opts -> Ok opts { optMcpu = read n }) "RATIO")
210 0427285d Iustin Pop
          "maximum virtual-to-physical cpu ratio for nodes"
211 0427285d Iustin Pop
212 df18fdfe Iustin Pop
oMaxSolLength :: OptType
213 df18fdfe Iustin Pop
oMaxSolLength = Option "l" ["max-length"]
214 df18fdfe Iustin Pop
                (ReqArg (\ i opts -> Ok opts { optMaxLength = read i }) "N")
215 df18fdfe Iustin Pop
                "cap the solution at this many moves (useful for very\
216 df18fdfe Iustin Pop
                \ unbalanced clusters)"
217 df18fdfe Iustin Pop
218 0427285d Iustin Pop
oMinDisk :: OptType
219 0427285d Iustin Pop
oMinDisk = Option "" ["min-disk"]
220 2f567ac0 Iustin Pop
           (ReqArg (\ n opts -> Ok opts { optMdsk = read n }) "RATIO")
221 0427285d Iustin Pop
           "minimum free disk space for nodes (between 0 and 1)"
222 0427285d Iustin Pop
223 df18fdfe Iustin Pop
oMinScore :: OptType
224 df18fdfe Iustin Pop
oMinScore = Option "e" ["min-score"]
225 df18fdfe Iustin Pop
            (ReqArg (\ e opts -> Ok opts { optMinScore = read e }) "EPSILON")
226 df18fdfe Iustin Pop
            " mininum score to aim for"
227 c0501c69 Iustin Pop
228 df18fdfe Iustin Pop
oNoHeaders :: OptType
229 df18fdfe Iustin Pop
oNoHeaders = Option "" ["no-headers"]
230 df18fdfe Iustin Pop
             (NoArg (\ opts -> Ok opts { optNoHeaders = True }))
231 df18fdfe Iustin Pop
             "do not show a header line"
232 4f83a560 Iustin Pop
233 df18fdfe Iustin Pop
oNodeSim :: OptType
234 df18fdfe Iustin Pop
oNodeSim = Option "" ["simulate"]
235 df18fdfe Iustin Pop
            (ReqArg (\ f o -> Ok o { optNodeSim = Just f }) "SPEC")
236 df18fdfe Iustin Pop
            "simulate an empty cluster, given as 'num_nodes,disk,ram,cpu'"
237 df18fdfe Iustin Pop
238 df18fdfe Iustin Pop
oOfflineNode :: OptType
239 df18fdfe Iustin Pop
oOfflineNode = Option "O" ["offline"]
240 df18fdfe Iustin Pop
               (ReqArg (\ n o -> Ok o { optOffline = n:optOffline o }) "NODE")
241 df18fdfe Iustin Pop
               "set node as offline"
242 df18fdfe Iustin Pop
243 df18fdfe Iustin Pop
oOneline :: OptType
244 df18fdfe Iustin Pop
oOneline = Option "o" ["oneline"]
245 df18fdfe Iustin Pop
           (NoArg (\ opts -> Ok opts { optOneline = True }))
246 df18fdfe Iustin Pop
           "print the ganeti command list for reaching the solution"
247 df18fdfe Iustin Pop
248 df18fdfe Iustin Pop
oOutputDir :: OptType
249 df18fdfe Iustin Pop
oOutputDir = Option "d" ["output-dir"]
250 df18fdfe Iustin Pop
             (ReqArg (\ d opts -> Ok opts { optOutPath = d }) "PATH")
251 df18fdfe Iustin Pop
             "directory in which to write output files"
252 df18fdfe Iustin Pop
253 df18fdfe Iustin Pop
oPrintCommands :: OptType
254 df18fdfe Iustin Pop
oPrintCommands = Option "C" ["print-commands"]
255 df18fdfe Iustin Pop
                 (OptArg ((\ f opts -> Ok opts { optShowCmds = Just f }) .
256 df18fdfe Iustin Pop
                          fromMaybe "-")
257 df18fdfe Iustin Pop
                  "FILE")
258 df18fdfe Iustin Pop
                 "print the ganeti command list for reaching the solution,\
259 df18fdfe Iustin Pop
                 \ if an argument is passed then write the commands to a\
260 df18fdfe Iustin Pop
                 \ file named as such"
261 df18fdfe Iustin Pop
262 df18fdfe Iustin Pop
oPrintInsts :: OptType
263 df18fdfe Iustin Pop
oPrintInsts = Option "" ["print-instances"]
264 df18fdfe Iustin Pop
              (NoArg (\ opts -> Ok opts { optShowInsts = True }))
265 df18fdfe Iustin Pop
              "print the final instance map"
266 df18fdfe Iustin Pop
267 df18fdfe Iustin Pop
oPrintNodes :: OptType
268 df18fdfe Iustin Pop
oPrintNodes = Option "p" ["print-nodes"]
269 df18fdfe Iustin Pop
              (OptArg ((\ f opts ->
270 df18fdfe Iustin Pop
                            let splitted = sepSplit ',' f
271 df18fdfe Iustin Pop
                            in Ok opts { optShowNodes = Just splitted }) .
272 df18fdfe Iustin Pop
                       fromMaybe []) "FIELDS")
273 df18fdfe Iustin Pop
              "print the final node list"
274 df18fdfe Iustin Pop
275 df18fdfe Iustin Pop
oQuiet :: OptType
276 df18fdfe Iustin Pop
oQuiet = Option "q" ["quiet"]
277 df18fdfe Iustin Pop
         (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts - 1 }))
278 df18fdfe Iustin Pop
         "decrease the verbosity level"
279 df18fdfe Iustin Pop
280 df18fdfe Iustin Pop
oRapiMaster :: OptType
281 df18fdfe Iustin Pop
oRapiMaster = Option "m" ["master"]
282 df18fdfe Iustin Pop
              (ReqArg (\ m opts -> Ok opts { optMaster = m }) "ADDRESS")
283 df18fdfe Iustin Pop
              "collect data via RAPI at the given ADDRESS"
284 df18fdfe Iustin Pop
285 df18fdfe Iustin Pop
oShowHelp :: OptType
286 df18fdfe Iustin Pop
oShowHelp = Option "h" ["help"]
287 df18fdfe Iustin Pop
            (NoArg (\ opts -> Ok opts { optShowHelp = True}))
288 df18fdfe Iustin Pop
            "show help"
289 df18fdfe Iustin Pop
290 df18fdfe Iustin Pop
oShowVer :: OptType
291 df18fdfe Iustin Pop
oShowVer = Option "V" ["version"]
292 df18fdfe Iustin Pop
           (NoArg (\ opts -> Ok opts { optShowVer = True}))
293 df18fdfe Iustin Pop
           "show the version of the program"
294 0f15cc76 Iustin Pop
295 1f9066c0 Iustin Pop
oTieredSpec :: OptType
296 1f9066c0 Iustin Pop
oTieredSpec = Option "" ["tiered-alloc"]
297 1f9066c0 Iustin Pop
             (ReqArg (\ inp opts -> do
298 1f9066c0 Iustin Pop
                          let sp = sepSplit ',' inp
299 1f9066c0 Iustin Pop
                          prs <- mapM (tryRead "tiered specs") sp
300 1f9066c0 Iustin Pop
                          tspec <-
301 1f9066c0 Iustin Pop
                              case prs of
302 7f4e37f0 Iustin Pop
                                [dsk, ram, cpu] -> return $ RSpec cpu ram dsk
303 1f9066c0 Iustin Pop
                                _ -> Bad $ "Invalid specification: " ++ inp
304 1f9066c0 Iustin Pop
                          return $ opts { optTieredSpec = Just tspec } )
305 1f9066c0 Iustin Pop
              "TSPEC")
306 7f4e37f0 Iustin Pop
             "enable tiered specs allocation, given as 'disk,ram,cpu'"
307 1f9066c0 Iustin Pop
308 df18fdfe Iustin Pop
oVerbose :: OptType
309 df18fdfe Iustin Pop
oVerbose = Option "v" ["verbose"]
310 df18fdfe Iustin Pop
           (NoArg (\ opts -> Ok opts { optVerbose = optVerbose opts + 1 }))
311 df18fdfe Iustin Pop
           "increase the verbosity level"
312 fae371cc Iustin Pop
313 78694255 Iustin Pop
-- | Usage info
314 0427285d Iustin Pop
usageHelp :: String -> [OptType] -> String
315 9f6dcdea Iustin Pop
usageHelp progname =
316 78694255 Iustin Pop
    usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
317 9f6dcdea Iustin Pop
               progname Version.version progname)
318 78694255 Iustin Pop
319 209b3711 Iustin Pop
-- | Command line parser, using the 'options' structure.
320 0427285d Iustin Pop
parseOpts :: [String]               -- ^ The command line arguments
321 0427285d Iustin Pop
          -> String                 -- ^ The program name
322 0427285d Iustin Pop
          -> [OptType]              -- ^ The supported command line options
323 0427285d Iustin Pop
          -> IO (Options, [String]) -- ^ The resulting options and leftover
324 0427285d Iustin Pop
                                    -- arguments
325 0427285d Iustin Pop
parseOpts argv progname options =
326 209b3711 Iustin Pop
    case getOpt Permute options argv of
327 209b3711 Iustin Pop
      (o, n, []) ->
328 209b3711 Iustin Pop
          do
329 2f567ac0 Iustin Pop
            let (pr, args) = (foldM (flip id) defaultOptions o, n)
330 2f567ac0 Iustin Pop
            po <- (case pr of
331 2f567ac0 Iustin Pop
                     Bad msg -> do
332 2f567ac0 Iustin Pop
                       hPutStrLn stderr "Error while parsing command\
333 2f567ac0 Iustin Pop
                                        \line arguments:"
334 2f567ac0 Iustin Pop
                       hPutStrLn stderr msg
335 2f567ac0 Iustin Pop
                       exitWith $ ExitFailure 1
336 2f567ac0 Iustin Pop
                     Ok val -> return val)
337 0427285d Iustin Pop
            when (optShowHelp po) $ do
338 78694255 Iustin Pop
              putStr $ usageHelp progname options
339 209b3711 Iustin Pop
              exitWith ExitSuccess
340 0427285d Iustin Pop
            when (optShowVer po) $ do
341 75d1edf8 Iustin Pop
              printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
342 75d1edf8 Iustin Pop
                     progname Version.version
343 75d1edf8 Iustin Pop
                     compilerName (Data.Version.showVersion compilerVersion)
344 75d1edf8 Iustin Pop
                     os arch
345 75d1edf8 Iustin Pop
              exitWith ExitSuccess
346 2f567ac0 Iustin Pop
            return (po, args)
347 f723de38 Iustin Pop
      (_, _, errs) -> do
348 f723de38 Iustin Pop
        hPutStrLn stderr $ "Command line error: "  ++ concat errs
349 f723de38 Iustin Pop
        hPutStrLn stderr $ usageHelp progname options
350 f723de38 Iustin Pop
        exitWith $ ExitFailure 2
351 209b3711 Iustin Pop
352 9188aeef Iustin Pop
-- | A shell script template for autogenerated scripts.
353 e0eb63f0 Iustin Pop
shTemplate :: String
354 e0eb63f0 Iustin Pop
shTemplate =
355 e0eb63f0 Iustin Pop
    printf "#!/bin/sh\n\n\
356 e0eb63f0 Iustin Pop
           \# Auto-generated script for executing cluster rebalancing\n\n\
357 e0eb63f0 Iustin Pop
           \# To stop, touch the file /tmp/stop-htools\n\n\
358 e0eb63f0 Iustin Pop
           \set -e\n\n\
359 e0eb63f0 Iustin Pop
           \check() {\n\
360 e0eb63f0 Iustin Pop
           \  if [ -f /tmp/stop-htools ]; then\n\
361 e0eb63f0 Iustin Pop
           \    echo 'Stop requested, exiting'\n\
362 e0eb63f0 Iustin Pop
           \    exit 0\n\
363 e0eb63f0 Iustin Pop
           \  fi\n\
364 e0eb63f0 Iustin Pop
           \}\n\n"