Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Common.hs @ 7b9ceea7

History | View | Annotate | Download (13.3 kB)

1 51000365 Iustin Pop
{-| Base common functionality.
2 51000365 Iustin Pop
3 51000365 Iustin Pop
This module holds common functionality shared across Ganeti daemons,
4 51000365 Iustin Pop
HTools and any other programs.
5 51000365 Iustin Pop
6 51000365 Iustin Pop
-}
7 51000365 Iustin Pop
8 51000365 Iustin Pop
{-
9 51000365 Iustin Pop
10 9fb621af Yiannis Tsiouris
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
11 51000365 Iustin Pop
12 51000365 Iustin Pop
This program is free software; you can redistribute it and/or modify
13 51000365 Iustin Pop
it under the terms of the GNU General Public License as published by
14 51000365 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 51000365 Iustin Pop
(at your option) any later version.
16 51000365 Iustin Pop
17 51000365 Iustin Pop
This program is distributed in the hope that it will be useful, but
18 51000365 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 51000365 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 51000365 Iustin Pop
General Public License for more details.
21 51000365 Iustin Pop
22 51000365 Iustin Pop
You should have received a copy of the GNU General Public License
23 51000365 Iustin Pop
along with this program; if not, write to the Free Software
24 51000365 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 51000365 Iustin Pop
02110-1301, USA.
26 51000365 Iustin Pop
27 51000365 Iustin Pop
-}
28 51000365 Iustin Pop
29 51000365 Iustin Pop
module Ganeti.Common
30 51000365 Iustin Pop
  ( GenericOptType
31 51000365 Iustin Pop
  , StandardOptions(..)
32 f5af3409 Iustin Pop
  , OptCompletion(..)
33 a6cdfdcc Iustin Pop
  , ArgCompletion(..)
34 2e6ef129 Iustin Pop
  , PersonalityList
35 f5af3409 Iustin Pop
  , optComplYesNo
36 51000365 Iustin Pop
  , oShowHelp
37 51000365 Iustin Pop
  , oShowVer
38 097ad7ee Iustin Pop
  , oShowComp
39 51000365 Iustin Pop
  , usageHelp
40 51000365 Iustin Pop
  , versionInfo
41 814e1e23 Iustin Pop
  , formatCommands
42 51000365 Iustin Pop
  , reqWithConversion
43 51000365 Iustin Pop
  , parseYesNo
44 51000365 Iustin Pop
  , parseOpts
45 51000365 Iustin Pop
  , parseOptsInner
46 630c73e5 Iustin Pop
  , parseOptsCmds
47 630c73e5 Iustin Pop
  , genericMainCmds
48 51000365 Iustin Pop
  ) where
49 51000365 Iustin Pop
50 51000365 Iustin Pop
import Control.Monad (foldM)
51 097ad7ee Iustin Pop
import Data.Char (toLower)
52 630c73e5 Iustin Pop
import Data.List (intercalate, stripPrefix, sortBy)
53 097ad7ee Iustin Pop
import Data.Maybe (fromMaybe)
54 630c73e5 Iustin Pop
import Data.Ord (comparing)
55 51000365 Iustin Pop
import qualified Data.Version
56 51000365 Iustin Pop
import System.Console.GetOpt
57 630c73e5 Iustin Pop
import System.Environment
58 51000365 Iustin Pop
import System.Exit
59 51000365 Iustin Pop
import System.Info
60 51000365 Iustin Pop
import System.IO
61 51000365 Iustin Pop
import Text.Printf (printf)
62 51000365 Iustin Pop
63 51000365 Iustin Pop
import Ganeti.BasicTypes
64 630c73e5 Iustin Pop
import qualified Ganeti.Constants as C
65 9fb621af Yiannis Tsiouris
import Ganeti.Utils (wrap)
66 51000365 Iustin Pop
import qualified Ganeti.Version as Version (version)
67 51000365 Iustin Pop
68 f5af3409 Iustin Pop
-- | Parameter type.
69 f5af3409 Iustin Pop
data OptCompletion = OptComplNone             -- ^ No parameter to this option
70 f5af3409 Iustin Pop
                   | OptComplFile             -- ^ An existing file
71 f5af3409 Iustin Pop
                   | OptComplDir              -- ^ An existing directory
72 f5af3409 Iustin Pop
                   | OptComplHost             -- ^ Host name
73 f5af3409 Iustin Pop
                   | OptComplInetAddr         -- ^ One ipv4\/ipv6 address
74 f5af3409 Iustin Pop
                   | OptComplOneNode          -- ^ One node
75 f5af3409 Iustin Pop
                   | OptComplManyNodes        -- ^ Many nodes, comma-sep
76 f5af3409 Iustin Pop
                   | OptComplOneInstance      -- ^ One instance
77 f5af3409 Iustin Pop
                   | OptComplManyInstances    -- ^ Many instances, comma-sep
78 f5af3409 Iustin Pop
                   | OptComplOneOs            -- ^ One OS name
79 f5af3409 Iustin Pop
                   | OptComplOneIallocator    -- ^ One iallocator
80 f5af3409 Iustin Pop
                   | OptComplInstAddNodes     -- ^ Either one or two nodes
81 f5af3409 Iustin Pop
                   | OptComplOneGroup         -- ^ One group
82 ecebe9f6 Iustin Pop
                   | OptComplInteger          -- ^ Integer values
83 ecebe9f6 Iustin Pop
                   | OptComplFloat            -- ^ Float values
84 a6cdfdcc Iustin Pop
                   | OptComplJobId            -- ^ Job Id
85 a6cdfdcc Iustin Pop
                   | OptComplCommand          -- ^ Command (executable)
86 f5af3409 Iustin Pop
                   | OptComplString           -- ^ Arbitrary string
87 f5af3409 Iustin Pop
                   | OptComplChoices [String] -- ^ List of string choices
88 a6cdfdcc Iustin Pop
                   | OptComplSuggest [String] -- ^ Suggested choices
89 139c0683 Iustin Pop
                   deriving (Show, Eq)
90 f5af3409 Iustin Pop
91 a6cdfdcc Iustin Pop
-- | Argument type. This differs from (and wraps) an Option by the
92 a6cdfdcc Iustin Pop
-- fact that it can (and usually does) support multiple repetitions of
93 a6cdfdcc Iustin Pop
-- the same argument, via a min and max limit.
94 a6cdfdcc Iustin Pop
data ArgCompletion = ArgCompletion OptCompletion Int (Maybe Int)
95 139c0683 Iustin Pop
                     deriving (Show, Eq)
96 a6cdfdcc Iustin Pop
97 2e6ef129 Iustin Pop
-- | A personality definition.
98 2e6ef129 Iustin Pop
type Personality a = ( a -> [String] -> IO () -- The main function
99 2e6ef129 Iustin Pop
                     , IO [GenericOptType a]  -- The options
100 2e6ef129 Iustin Pop
                     , [ArgCompletion]        -- The description of args
101 559c4a98 Iustin Pop
                     , String                 -- Description
102 2e6ef129 Iustin Pop
                     )
103 2e6ef129 Iustin Pop
104 2e6ef129 Iustin Pop
-- | Personality lists type, common across all binaries that expose
105 2e6ef129 Iustin Pop
-- multiple personalities.
106 2e6ef129 Iustin Pop
type PersonalityList  a = [(String, Personality a)]
107 2e6ef129 Iustin Pop
108 f5af3409 Iustin Pop
-- | Yes\/no choices completion.
109 f5af3409 Iustin Pop
optComplYesNo :: OptCompletion
110 f5af3409 Iustin Pop
optComplYesNo = OptComplChoices ["yes", "no"]
111 f5af3409 Iustin Pop
112 097ad7ee Iustin Pop
-- | Text serialisation for 'OptCompletion', used on the Python side.
113 097ad7ee Iustin Pop
complToText :: OptCompletion -> String
114 fad06963 Iustin Pop
complToText (OptComplChoices choices) = "choices=" ++ intercalate "," choices
115 fad06963 Iustin Pop
complToText (OptComplSuggest choices) = "suggest=" ++ intercalate "," choices
116 097ad7ee Iustin Pop
complToText compl =
117 097ad7ee Iustin Pop
  let show_compl = show compl
118 097ad7ee Iustin Pop
      stripped = stripPrefix "OptCompl" show_compl
119 097ad7ee Iustin Pop
  in map toLower $ fromMaybe show_compl stripped
120 097ad7ee Iustin Pop
121 7ce2f8ee Michele Tartara
-- | Text serialisation for 'ArgCompletion'.
122 a6cdfdcc Iustin Pop
argComplToText :: ArgCompletion -> String
123 a6cdfdcc Iustin Pop
argComplToText (ArgCompletion optc min_cnt max_cnt) =
124 a6cdfdcc Iustin Pop
  complToText optc ++ " " ++ show min_cnt ++ " " ++ maybe "none" show max_cnt
125 a6cdfdcc Iustin Pop
126 f5606cda Dato Simรณ
-- | Abbreviation for the option type.
127 ce207617 Iustin Pop
type GenericOptType a = (OptDescr (a -> Result a), OptCompletion)
128 51000365 Iustin Pop
129 51000365 Iustin Pop
-- | Type class for options which support help and version.
130 51000365 Iustin Pop
class StandardOptions a where
131 51000365 Iustin Pop
  helpRequested :: a -> Bool
132 51000365 Iustin Pop
  verRequested  :: a -> Bool
133 097ad7ee Iustin Pop
  compRequested :: a -> Bool
134 51000365 Iustin Pop
  requestHelp   :: a -> a
135 51000365 Iustin Pop
  requestVer    :: a -> a
136 097ad7ee Iustin Pop
  requestComp   :: a -> a
137 51000365 Iustin Pop
138 097ad7ee Iustin Pop
-- | Option to request help output.
139 51000365 Iustin Pop
oShowHelp :: (StandardOptions a) => GenericOptType a
140 ce207617 Iustin Pop
oShowHelp = (Option "h" ["help"] (NoArg (Ok . requestHelp)) "show help",
141 ce207617 Iustin Pop
             OptComplNone)
142 51000365 Iustin Pop
143 ce207617 Iustin Pop
-- | Option to request version information.
144 51000365 Iustin Pop
oShowVer :: (StandardOptions a) => GenericOptType a
145 ce207617 Iustin Pop
oShowVer = (Option "V" ["version"] (NoArg (Ok . requestVer))
146 ce207617 Iustin Pop
            "show the version of the program",
147 ce207617 Iustin Pop
            OptComplNone)
148 51000365 Iustin Pop
149 097ad7ee Iustin Pop
-- | Option to request completion information
150 097ad7ee Iustin Pop
oShowComp :: (StandardOptions a) => GenericOptType a
151 097ad7ee Iustin Pop
oShowComp =
152 097ad7ee Iustin Pop
  (Option "" ["help-completion"] (NoArg (Ok . requestComp) )
153 097ad7ee Iustin Pop
   "show completion info", OptComplNone)
154 097ad7ee Iustin Pop
155 51000365 Iustin Pop
-- | Usage info.
156 51000365 Iustin Pop
usageHelp :: String -> [GenericOptType a] -> String
157 51000365 Iustin Pop
usageHelp progname =
158 51000365 Iustin Pop
  usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
159 ce207617 Iustin Pop
             progname Version.version progname) . map fst
160 51000365 Iustin Pop
161 51000365 Iustin Pop
-- | Show the program version info.
162 51000365 Iustin Pop
versionInfo :: String -> String
163 51000365 Iustin Pop
versionInfo progname =
164 51000365 Iustin Pop
  printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
165 51000365 Iustin Pop
         progname Version.version compilerName
166 51000365 Iustin Pop
         (Data.Version.showVersion compilerVersion)
167 51000365 Iustin Pop
         os arch
168 51000365 Iustin Pop
169 097ad7ee Iustin Pop
-- | Show completion info.
170 a6cdfdcc Iustin Pop
completionInfo :: String -> [GenericOptType a] -> [ArgCompletion] -> String
171 a6cdfdcc Iustin Pop
completionInfo _ opts args =
172 a6cdfdcc Iustin Pop
  unlines $
173 097ad7ee Iustin Pop
  map (\(Option shorts longs _ _, compinfo) ->
174 097ad7ee Iustin Pop
         let all_opts = map (\c -> ['-', c]) shorts ++ map ("--" ++) longs
175 097ad7ee Iustin Pop
         in intercalate "," all_opts ++ " " ++ complToText compinfo
176 a6cdfdcc Iustin Pop
      ) opts ++
177 a6cdfdcc Iustin Pop
  map argComplToText args
178 097ad7ee Iustin Pop
179 51000365 Iustin Pop
-- | Helper for parsing a yes\/no command line flag.
180 51000365 Iustin Pop
parseYesNo :: Bool         -- ^ Default value (when we get a @Nothing@)
181 51000365 Iustin Pop
           -> Maybe String -- ^ Parameter value
182 51000365 Iustin Pop
           -> Result Bool  -- ^ Resulting boolean value
183 51000365 Iustin Pop
parseYesNo v Nothing      = return v
184 51000365 Iustin Pop
parseYesNo _ (Just "yes") = return True
185 51000365 Iustin Pop
parseYesNo _ (Just "no")  = return False
186 51000365 Iustin Pop
parseYesNo _ (Just s)     = fail ("Invalid choice '" ++ s ++
187 51000365 Iustin Pop
                                  "', pass one of 'yes' or 'no'")
188 51000365 Iustin Pop
189 51000365 Iustin Pop
-- | Helper function for required arguments which need to be converted
190 51000365 Iustin Pop
-- as opposed to stored just as string.
191 51000365 Iustin Pop
reqWithConversion :: (String -> Result a)
192 51000365 Iustin Pop
                  -> (a -> b -> Result b)
193 51000365 Iustin Pop
                  -> String
194 51000365 Iustin Pop
                  -> ArgDescr (b -> Result b)
195 5b11f8db Iustin Pop
reqWithConversion conversion_fn updater_fn =
196 51000365 Iustin Pop
  ReqArg (\string_opt opts -> do
197 51000365 Iustin Pop
            parsed_value <- conversion_fn string_opt
198 5b11f8db Iustin Pop
            updater_fn parsed_value opts)
199 51000365 Iustin Pop
200 630c73e5 Iustin Pop
-- | Max command length when formatting command list output.
201 630c73e5 Iustin Pop
maxCmdLen :: Int
202 630c73e5 Iustin Pop
maxCmdLen = 60
203 630c73e5 Iustin Pop
204 814e1e23 Iustin Pop
-- | Formats the description of various commands.
205 814e1e23 Iustin Pop
formatCommands :: (StandardOptions a) => PersonalityList a -> [String]
206 814e1e23 Iustin Pop
formatCommands personalities =
207 9fb621af Yiannis Tsiouris
  concatMap (\(cmd, (_, _, _, desc)) ->
208 9fb621af Yiannis Tsiouris
              fmtDesc cmd (wrap maxWidth desc) "-" []) $
209 814e1e23 Iustin Pop
  sortBy (comparing fst) personalities
210 814e1e23 Iustin Pop
    where mlen = min maxCmdLen . maximum $ map (length . fst) personalities
211 9fb621af Yiannis Tsiouris
          maxWidth = 79 - 3 - mlen
212 9fb621af Yiannis Tsiouris
          fmtDesc _ [] _ acc = reverse acc
213 9fb621af Yiannis Tsiouris
          fmtDesc cmd (d : ds) sep acc =
214 9fb621af Yiannis Tsiouris
            fmtDesc "" ds " " (printf " %-*s %s %s" mlen cmd sep d : acc)
215 814e1e23 Iustin Pop
216 630c73e5 Iustin Pop
-- | Formats usage for a multi-personality program.
217 630c73e5 Iustin Pop
formatCmdUsage :: (StandardOptions a) => String -> PersonalityList a -> String
218 630c73e5 Iustin Pop
formatCmdUsage prog personalities =
219 814e1e23 Iustin Pop
  let header = [ printf "Usage: %s {command} [options...] [argument...]" prog
220 630c73e5 Iustin Pop
               , printf "%s <command> --help to see details, or man %s"
221 630c73e5 Iustin Pop
                   prog prog
222 630c73e5 Iustin Pop
               , ""
223 630c73e5 Iustin Pop
               , "Commands:"
224 630c73e5 Iustin Pop
               ]
225 814e1e23 Iustin Pop
      rows = formatCommands personalities
226 630c73e5 Iustin Pop
  in unlines $ header ++ rows
227 630c73e5 Iustin Pop
228 630c73e5 Iustin Pop
-- | Displays usage for a program and exits.
229 630c73e5 Iustin Pop
showCmdUsage :: (StandardOptions a) =>
230 630c73e5 Iustin Pop
                String            -- ^ Program name
231 630c73e5 Iustin Pop
             -> PersonalityList a -- ^ Personality list
232 630c73e5 Iustin Pop
             -> Bool              -- ^ Whether the exit code is success or not
233 630c73e5 Iustin Pop
             -> IO b
234 630c73e5 Iustin Pop
showCmdUsage prog personalities success = do
235 630c73e5 Iustin Pop
  let usage = formatCmdUsage prog personalities
236 630c73e5 Iustin Pop
  putStr usage
237 630c73e5 Iustin Pop
  if success
238 630c73e5 Iustin Pop
    then exitSuccess
239 630c73e5 Iustin Pop
    else exitWith $ ExitFailure C.exitFailure
240 630c73e5 Iustin Pop
241 daf0de68 Iustin Pop
-- | Generates completion information for a multi-command binary.
242 daf0de68 Iustin Pop
multiCmdCompletion :: (StandardOptions a) => PersonalityList a -> String
243 daf0de68 Iustin Pop
multiCmdCompletion personalities =
244 7ce2f8ee Michele Tartara
  argComplToText $
245 7ce2f8ee Michele Tartara
    ArgCompletion (OptComplChoices (map fst personalities))
246 7ce2f8ee Michele Tartara
      1 (Just 1)
247 daf0de68 Iustin Pop
248 daf0de68 Iustin Pop
-- | Displays completion information for a multi-command binary and exits.
249 daf0de68 Iustin Pop
showCmdCompletion :: (StandardOptions a) => PersonalityList a -> IO b
250 daf0de68 Iustin Pop
showCmdCompletion personalities =
251 7ce2f8ee Michele Tartara
  putStrLn (multiCmdCompletion personalities) >> exitSuccess
252 daf0de68 Iustin Pop
253 51000365 Iustin Pop
-- | Command line parser, using a generic 'Options' structure.
254 51000365 Iustin Pop
parseOpts :: (StandardOptions a) =>
255 51000365 Iustin Pop
             a                      -- ^ The default options
256 51000365 Iustin Pop
          -> [String]               -- ^ The command line arguments
257 51000365 Iustin Pop
          -> String                 -- ^ The program name
258 51000365 Iustin Pop
          -> [GenericOptType a]     -- ^ The supported command line options
259 22278fa7 Iustin Pop
          -> [ArgCompletion]        -- ^ The supported command line arguments
260 51000365 Iustin Pop
          -> IO (a, [String])       -- ^ The resulting options and
261 51000365 Iustin Pop
                                    -- leftover arguments
262 22278fa7 Iustin Pop
parseOpts defaults argv progname options arguments =
263 22278fa7 Iustin Pop
  case parseOptsInner defaults argv progname options arguments of
264 51000365 Iustin Pop
    Left (code, msg) -> do
265 51000365 Iustin Pop
      hPutStr (if code == ExitSuccess then stdout else stderr) msg
266 51000365 Iustin Pop
      exitWith code
267 51000365 Iustin Pop
    Right result ->
268 51000365 Iustin Pop
      return result
269 51000365 Iustin Pop
270 630c73e5 Iustin Pop
-- | Command line parser, for programs with sub-commands.
271 630c73e5 Iustin Pop
parseOptsCmds :: (StandardOptions a) =>
272 630c73e5 Iustin Pop
                 a                      -- ^ The default options
273 630c73e5 Iustin Pop
              -> [String]               -- ^ The command line arguments
274 630c73e5 Iustin Pop
              -> String                 -- ^ The program name
275 630c73e5 Iustin Pop
              -> PersonalityList a      -- ^ The supported commands
276 630c73e5 Iustin Pop
              -> [GenericOptType a]     -- ^ Generic options
277 630c73e5 Iustin Pop
              -> IO (a, [String], a -> [String] -> IO ())
278 630c73e5 Iustin Pop
                     -- ^ The resulting options and leftover arguments
279 630c73e5 Iustin Pop
parseOptsCmds defaults argv progname personalities genopts = do
280 630c73e5 Iustin Pop
  let usage = showCmdUsage progname personalities
281 630c73e5 Iustin Pop
      check c = case c of
282 630c73e5 Iustin Pop
                  -- hardcoded option strings here!
283 630c73e5 Iustin Pop
                  "--version" -> putStrLn (versionInfo progname) >> exitSuccess
284 630c73e5 Iustin Pop
                  "--help"    -> usage True
285 daf0de68 Iustin Pop
                  "--help-completion" -> showCmdCompletion personalities
286 630c73e5 Iustin Pop
                  _           -> return c
287 630c73e5 Iustin Pop
  (cmd, cmd_args) <- case argv of
288 630c73e5 Iustin Pop
                       cmd:cmd_args -> do
289 630c73e5 Iustin Pop
                         cmd' <- check cmd
290 630c73e5 Iustin Pop
                         return (cmd', cmd_args)
291 630c73e5 Iustin Pop
                       [] -> usage False
292 630c73e5 Iustin Pop
  case cmd `lookup` personalities of
293 630c73e5 Iustin Pop
    Nothing -> usage False
294 559c4a98 Iustin Pop
    Just (mainfn, optdefs, argdefs, _) -> do
295 630c73e5 Iustin Pop
      optdefs' <- optdefs
296 630c73e5 Iustin Pop
      (opts, args) <- parseOpts defaults cmd_args progname
297 630c73e5 Iustin Pop
                      (optdefs' ++ genopts) argdefs
298 630c73e5 Iustin Pop
      return (opts, args, mainfn)
299 630c73e5 Iustin Pop
300 51000365 Iustin Pop
-- | Inner parse options. The arguments are similar to 'parseOpts',
301 51000365 Iustin Pop
-- but it returns either a 'Left' composed of exit code and message,
302 51000365 Iustin Pop
-- or a 'Right' for the success case.
303 51000365 Iustin Pop
parseOptsInner :: (StandardOptions a) =>
304 51000365 Iustin Pop
                  a
305 51000365 Iustin Pop
               -> [String]
306 51000365 Iustin Pop
               -> String
307 51000365 Iustin Pop
               -> [GenericOptType a]
308 22278fa7 Iustin Pop
               -> [ArgCompletion]
309 51000365 Iustin Pop
               -> Either (ExitCode, String) (a, [String])
310 22278fa7 Iustin Pop
parseOptsInner defaults argv progname options arguments  =
311 ce207617 Iustin Pop
  case getOpt Permute (map fst options) argv of
312 51000365 Iustin Pop
    (opts, args, []) ->
313 51000365 Iustin Pop
      case foldM (flip id) defaults opts of
314 51000365 Iustin Pop
           Bad msg -> Left (ExitFailure 1,
315 51000365 Iustin Pop
                            "Error while parsing command line arguments:\n"
316 51000365 Iustin Pop
                            ++ msg ++ "\n")
317 51000365 Iustin Pop
           Ok parsed ->
318 51000365 Iustin Pop
             select (Right (parsed, args))
319 51000365 Iustin Pop
                 [ (helpRequested parsed,
320 51000365 Iustin Pop
                    Left (ExitSuccess, usageHelp progname options))
321 51000365 Iustin Pop
                 , (verRequested parsed,
322 51000365 Iustin Pop
                    Left (ExitSuccess, versionInfo progname))
323 097ad7ee Iustin Pop
                 , (compRequested parsed,
324 22278fa7 Iustin Pop
                    Left (ExitSuccess, completionInfo progname options
325 22278fa7 Iustin Pop
                                         arguments))
326 51000365 Iustin Pop
                 ]
327 51000365 Iustin Pop
    (_, _, errs) ->
328 51000365 Iustin Pop
      Left (ExitFailure 2, "Command line error: "  ++ concat errs ++ "\n" ++
329 51000365 Iustin Pop
            usageHelp progname options)
330 630c73e5 Iustin Pop
331 630c73e5 Iustin Pop
-- | Parse command line options and execute the main function of a
332 630c73e5 Iustin Pop
-- multi-personality binary.
333 630c73e5 Iustin Pop
genericMainCmds :: (StandardOptions a) =>
334 630c73e5 Iustin Pop
                   a
335 630c73e5 Iustin Pop
                -> PersonalityList a
336 630c73e5 Iustin Pop
                -> [GenericOptType a]
337 630c73e5 Iustin Pop
                -> IO ()
338 630c73e5 Iustin Pop
genericMainCmds defaults personalities genopts = do
339 630c73e5 Iustin Pop
  cmd_args <- getArgs
340 630c73e5 Iustin Pop
  prog <- getProgName
341 630c73e5 Iustin Pop
  (opts, args, fn) <-
342 630c73e5 Iustin Pop
    parseOptsCmds defaults cmd_args prog personalities genopts
343 630c73e5 Iustin Pop
  fn opts args