Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Common.hs @ 54c7dff7

History | View | Annotate | Download (13.3 kB)

1
{-| Base common functionality.
2

    
3
This module holds common functionality shared across Ganeti daemons,
4
HTools and any other programs.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
11

    
12
This program is free software; you can redistribute it and/or modify
13
it under the terms of the GNU General Public License as published by
14
the Free Software Foundation; either version 2 of the License, or
15
(at your option) any later version.
16

    
17
This program is distributed in the hope that it will be useful, but
18
WITHOUT ANY WARRANTY; without even the implied warranty of
19
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20
General Public License for more details.
21

    
22
You should have received a copy of the GNU General Public License
23
along with this program; if not, write to the Free Software
24
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25
02110-1301, USA.
26

    
27
-}
28

    
29
module Ganeti.Common
30
  ( GenericOptType
31
  , StandardOptions(..)
32
  , OptCompletion(..)
33
  , ArgCompletion(..)
34
  , PersonalityList
35
  , optComplYesNo
36
  , oShowHelp
37
  , oShowVer
38
  , oShowComp
39
  , usageHelp
40
  , versionInfo
41
  , formatCommands
42
  , reqWithConversion
43
  , parseYesNo
44
  , parseOpts
45
  , parseOptsInner
46
  , parseOptsCmds
47
  , genericMainCmds
48
  ) where
49

    
50
import Control.Monad (foldM)
51
import Data.Char (toLower)
52
import Data.List (intercalate, stripPrefix, sortBy)
53
import Data.Maybe (fromMaybe)
54
import Data.Ord (comparing)
55
import qualified Data.Version
56
import System.Console.GetOpt
57
import System.Environment
58
import System.Exit
59
import System.Info
60
import System.IO
61
import Text.Printf (printf)
62

    
63
import Ganeti.BasicTypes
64
import qualified Ganeti.Constants as C
65
import Ganeti.Utils (wrap)
66
import qualified Ganeti.Version as Version (version)
67

    
68
-- | Parameter type.
69
data OptCompletion = OptComplNone             -- ^ No parameter to this option
70
                   | OptComplFile             -- ^ An existing file
71
                   | OptComplDir              -- ^ An existing directory
72
                   | OptComplHost             -- ^ Host name
73
                   | OptComplInetAddr         -- ^ One ipv4\/ipv6 address
74
                   | OptComplOneNode          -- ^ One node
75
                   | OptComplManyNodes        -- ^ Many nodes, comma-sep
76
                   | OptComplOneInstance      -- ^ One instance
77
                   | OptComplManyInstances    -- ^ Many instances, comma-sep
78
                   | OptComplOneOs            -- ^ One OS name
79
                   | OptComplOneIallocator    -- ^ One iallocator
80
                   | OptComplInstAddNodes     -- ^ Either one or two nodes
81
                   | OptComplOneGroup         -- ^ One group
82
                   | OptComplInteger          -- ^ Integer values
83
                   | OptComplFloat            -- ^ Float values
84
                   | OptComplJobId            -- ^ Job Id
85
                   | OptComplCommand          -- ^ Command (executable)
86
                   | OptComplString           -- ^ Arbitrary string
87
                   | OptComplChoices [String] -- ^ List of string choices
88
                   | OptComplSuggest [String] -- ^ Suggested choices
89
                   deriving (Show, Eq)
90

    
91
-- | Argument type. This differs from (and wraps) an Option by the
92
-- fact that it can (and usually does) support multiple repetitions of
93
-- the same argument, via a min and max limit.
94
data ArgCompletion = ArgCompletion OptCompletion Int (Maybe Int)
95
                     deriving (Show, Eq)
96

    
97
-- | A personality definition.
98
type Personality a = ( a -> [String] -> IO () -- The main function
99
                     , IO [GenericOptType a]  -- The options
100
                     , [ArgCompletion]        -- The description of args
101
                     , String                 -- Description
102
                     )
103

    
104
-- | Personality lists type, common across all binaries that expose
105
-- multiple personalities.
106
type PersonalityList  a = [(String, Personality a)]
107

    
108
-- | Yes\/no choices completion.
109
optComplYesNo :: OptCompletion
110
optComplYesNo = OptComplChoices ["yes", "no"]
111

    
112
-- | Text serialisation for 'OptCompletion', used on the Python side.
113
complToText :: OptCompletion -> String
114
complToText (OptComplChoices choices) = "choices=" ++ intercalate "," choices
115
complToText (OptComplSuggest choices) = "suggest=" ++ intercalate "," choices
116
complToText compl =
117
  let show_compl = show compl
118
      stripped = stripPrefix "OptCompl" show_compl
119
  in map toLower $ fromMaybe show_compl stripped
120

    
121
-- | Text serialisation for 'ArgCompletion'.
122
argComplToText :: ArgCompletion -> String
123
argComplToText (ArgCompletion optc min_cnt max_cnt) =
124
  complToText optc ++ " " ++ show min_cnt ++ " " ++ maybe "none" show max_cnt
125

    
126
-- | Abbreviation for the option type.
127
type GenericOptType a = (OptDescr (a -> Result a), OptCompletion)
128

    
129
-- | Type class for options which support help and version.
130
class StandardOptions a where
131
  helpRequested :: a -> Bool
132
  verRequested  :: a -> Bool
133
  compRequested :: a -> Bool
134
  requestHelp   :: a -> a
135
  requestVer    :: a -> a
136
  requestComp   :: a -> a
137

    
138
-- | Option to request help output.
139
oShowHelp :: (StandardOptions a) => GenericOptType a
140
oShowHelp = (Option "h" ["help"] (NoArg (Ok . requestHelp)) "show help",
141
             OptComplNone)
142

    
143
-- | Option to request version information.
144
oShowVer :: (StandardOptions a) => GenericOptType a
145
oShowVer = (Option "V" ["version"] (NoArg (Ok . requestVer))
146
            "show the version of the program",
147
            OptComplNone)
148

    
149
-- | Option to request completion information
150
oShowComp :: (StandardOptions a) => GenericOptType a
151
oShowComp =
152
  (Option "" ["help-completion"] (NoArg (Ok . requestComp) )
153
   "show completion info", OptComplNone)
154

    
155
-- | Usage info.
156
usageHelp :: String -> [GenericOptType a] -> String
157
usageHelp progname =
158
  usageInfo (printf "%s %s\nUsage: %s [OPTION...]"
159
             progname Version.version progname) . map fst
160

    
161
-- | Show the program version info.
162
versionInfo :: String -> String
163
versionInfo progname =
164
  printf "%s %s\ncompiled with %s %s\nrunning on %s %s\n"
165
         progname Version.version compilerName
166
         (Data.Version.showVersion compilerVersion)
167
         os arch
168

    
169
-- | Show completion info.
170
completionInfo :: String -> [GenericOptType a] -> [ArgCompletion] -> String
171
completionInfo _ opts args =
172
  unlines $
173
  map (\(Option shorts longs _ _, compinfo) ->
174
         let all_opts = map (\c -> ['-', c]) shorts ++ map ("--" ++) longs
175
         in intercalate "," all_opts ++ " " ++ complToText compinfo
176
      ) opts ++
177
  map argComplToText args
178

    
179
-- | Helper for parsing a yes\/no command line flag.
180
parseYesNo :: Bool         -- ^ Default value (when we get a @Nothing@)
181
           -> Maybe String -- ^ Parameter value
182
           -> Result Bool  -- ^ Resulting boolean value
183
parseYesNo v Nothing      = return v
184
parseYesNo _ (Just "yes") = return True
185
parseYesNo _ (Just "no")  = return False
186
parseYesNo _ (Just s)     = fail ("Invalid choice '" ++ s ++
187
                                  "', pass one of 'yes' or 'no'")
188

    
189
-- | Helper function for required arguments which need to be converted
190
-- as opposed to stored just as string.
191
reqWithConversion :: (String -> Result a)
192
                  -> (a -> b -> Result b)
193
                  -> String
194
                  -> ArgDescr (b -> Result b)
195
reqWithConversion conversion_fn updater_fn =
196
  ReqArg (\string_opt opts -> do
197
            parsed_value <- conversion_fn string_opt
198
            updater_fn parsed_value opts)
199

    
200
-- | Max command length when formatting command list output.
201
maxCmdLen :: Int
202
maxCmdLen = 60
203

    
204
-- | Formats the description of various commands.
205
formatCommands :: (StandardOptions a) => PersonalityList a -> [String]
206
formatCommands personalities =
207
  concatMap (\(cmd, (_, _, _, desc)) ->
208
              fmtDesc cmd (wrap maxWidth desc) "-" []) $
209
  sortBy (comparing fst) personalities
210
    where mlen = min maxCmdLen . maximum $ map (length . fst) personalities
211
          maxWidth = 79 - 3 - mlen
212
          fmtDesc _ [] _ acc = reverse acc
213
          fmtDesc cmd (d : ds) sep acc =
214
            fmtDesc "" ds " " (printf " %-*s %s %s" mlen cmd sep d : acc)
215

    
216
-- | Formats usage for a multi-personality program.
217
formatCmdUsage :: (StandardOptions a) => String -> PersonalityList a -> String
218
formatCmdUsage prog personalities =
219
  let header = [ printf "Usage: %s {command} [options...] [argument...]" prog
220
               , printf "%s <command> --help to see details, or man %s"
221
                   prog prog
222
               , ""
223
               , "Commands:"
224
               ]
225
      rows = formatCommands personalities
226
  in unlines $ header ++ rows
227

    
228
-- | Displays usage for a program and exits.
229
showCmdUsage :: (StandardOptions a) =>
230
                String            -- ^ Program name
231
             -> PersonalityList a -- ^ Personality list
232
             -> Bool              -- ^ Whether the exit code is success or not
233
             -> IO b
234
showCmdUsage prog personalities success = do
235
  let usage = formatCmdUsage prog personalities
236
  putStr usage
237
  if success
238
    then exitSuccess
239
    else exitWith $ ExitFailure C.exitFailure
240

    
241
-- | Generates completion information for a multi-command binary.
242
multiCmdCompletion :: (StandardOptions a) => PersonalityList a -> String
243
multiCmdCompletion personalities =
244
  argComplToText $
245
    ArgCompletion (OptComplChoices (map fst personalities))
246
      1 (Just 1)
247

    
248
-- | Displays completion information for a multi-command binary and exits.
249
showCmdCompletion :: (StandardOptions a) => PersonalityList a -> IO b
250
showCmdCompletion personalities =
251
  putStrLn (multiCmdCompletion personalities) >> exitSuccess
252

    
253
-- | Command line parser, using a generic 'Options' structure.
254
parseOpts :: (StandardOptions a) =>
255
             a                      -- ^ The default options
256
          -> [String]               -- ^ The command line arguments
257
          -> String                 -- ^ The program name
258
          -> [GenericOptType a]     -- ^ The supported command line options
259
          -> [ArgCompletion]        -- ^ The supported command line arguments
260
          -> IO (a, [String])       -- ^ The resulting options and
261
                                    -- leftover arguments
262
parseOpts defaults argv progname options arguments =
263
  case parseOptsInner defaults argv progname options arguments of
264
    Left (code, msg) -> do
265
      hPutStr (if code == ExitSuccess then stdout else stderr) msg
266
      exitWith code
267
    Right result ->
268
      return result
269

    
270
-- | Command line parser, for programs with sub-commands.
271
parseOptsCmds :: (StandardOptions a) =>
272
                 a                      -- ^ The default options
273
              -> [String]               -- ^ The command line arguments
274
              -> String                 -- ^ The program name
275
              -> PersonalityList a      -- ^ The supported commands
276
              -> [GenericOptType a]     -- ^ Generic options
277
              -> IO (a, [String], a -> [String] -> IO ())
278
                     -- ^ The resulting options and leftover arguments
279
parseOptsCmds defaults argv progname personalities genopts = do
280
  let usage = showCmdUsage progname personalities
281
      check c = case c of
282
                  -- hardcoded option strings here!
283
                  "--version" -> putStrLn (versionInfo progname) >> exitSuccess
284
                  "--help"    -> usage True
285
                  "--help-completion" -> showCmdCompletion personalities
286
                  _           -> return c
287
  (cmd, cmd_args) <- case argv of
288
                       cmd:cmd_args -> do
289
                         cmd' <- check cmd
290
                         return (cmd', cmd_args)
291
                       [] -> usage False
292
  case cmd `lookup` personalities of
293
    Nothing -> usage False
294
    Just (mainfn, optdefs, argdefs, _) -> do
295
      optdefs' <- optdefs
296
      (opts, args) <- parseOpts defaults cmd_args progname
297
                      (optdefs' ++ genopts) argdefs
298
      return (opts, args, mainfn)
299

    
300
-- | Inner parse options. The arguments are similar to 'parseOpts',
301
-- but it returns either a 'Left' composed of exit code and message,
302
-- or a 'Right' for the success case.
303
parseOptsInner :: (StandardOptions a) =>
304
                  a
305
               -> [String]
306
               -> String
307
               -> [GenericOptType a]
308
               -> [ArgCompletion]
309
               -> Either (ExitCode, String) (a, [String])
310
parseOptsInner defaults argv progname options arguments  =
311
  case getOpt Permute (map fst options) argv of
312
    (opts, args, []) ->
313
      case foldM (flip id) defaults opts of
314
           Bad msg -> Left (ExitFailure 1,
315
                            "Error while parsing command line arguments:\n"
316
                            ++ msg ++ "\n")
317
           Ok parsed ->
318
             select (Right (parsed, args))
319
                 [ (helpRequested parsed,
320
                    Left (ExitSuccess, usageHelp progname options))
321
                 , (verRequested parsed,
322
                    Left (ExitSuccess, versionInfo progname))
323
                 , (compRequested parsed,
324
                    Left (ExitSuccess, completionInfo progname options
325
                                         arguments))
326
                 ]
327
    (_, _, errs) ->
328
      Left (ExitFailure 2, "Command line error: "  ++ concat errs ++ "\n" ++
329
            usageHelp progname options)
330

    
331
-- | Parse command line options and execute the main function of a
332
-- multi-personality binary.
333
genericMainCmds :: (StandardOptions a) =>
334
                   a
335
                -> PersonalityList a
336
                -> [GenericOptType a]
337
                -> IO ()
338
genericMainCmds defaults personalities genopts = do
339
  cmd_args <- getArgs
340
  prog <- getProgName
341
  (opts, args, fn) <-
342
    parseOptsCmds defaults cmd_args prog personalities genopts
343
  fn opts args