Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Common.hs @ 638e0a6f

History | View | Annotate | Download (13 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 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
  , reqWithConversion
42
  , parseYesNo
43
  , parseOpts
44
  , parseOptsInner
45
  , parseOptsCmds
46
  , genericMainCmds
47
  ) where
48

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

    
62
import Ganeti.BasicTypes
63
import qualified Ganeti.Constants as C
64
import qualified Ganeti.Version as Version (version)
65

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

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

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

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

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

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

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

    
124
-- | Abrreviation for the option type.
125
type GenericOptType a = (OptDescr (a -> Result a), OptCompletion)
126

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

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

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

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

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

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

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

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

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

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

    
202
-- | Formats usage for a multi-personality program.
203
formatCmdUsage :: (StandardOptions a) => String -> PersonalityList a -> String
204
formatCmdUsage prog personalities =
205
  let mlen = min maxCmdLen . maximum $ map (length . fst) personalities
206
      sorted = sortBy (comparing fst) personalities
207
      header = [ printf "Usage: %s {command} [options...] [argument...]" prog
208
               , printf "%s <command> --help to see details, or man %s"
209
                   prog prog
210
               , ""
211
               , "Commands:"
212
               ]
213
      rows = map (\(cmd, (_, _, _, desc)) ->
214
                    -- FIXME: not wrapped here
215
                    printf " %-*s - %s" mlen cmd desc::String) sorted
216
  in unlines $ header ++ rows
217

    
218
-- | Displays usage for a program and exits.
219
showCmdUsage :: (StandardOptions a) =>
220
                String            -- ^ Program name
221
             -> PersonalityList a -- ^ Personality list
222
             -> Bool              -- ^ Whether the exit code is success or not
223
             -> IO b
224
showCmdUsage prog personalities success = do
225
  let usage = formatCmdUsage prog personalities
226
  putStr usage
227
  if success
228
    then exitSuccess
229
    else exitWith $ ExitFailure C.exitFailure
230

    
231
-- | Generates completion information for a multi-command binary.
232
multiCmdCompletion :: (StandardOptions a) => PersonalityList a -> String
233
multiCmdCompletion personalities =
234
  unlines .
235
  map argComplToText $
236
  map (\(cmd, _) -> ArgCompletion (OptComplChoices [cmd]) 1 (Just 1))
237
    personalities
238

    
239
-- | Displays completion information for a multi-command binary and exits.
240
showCmdCompletion :: (StandardOptions a) => PersonalityList a -> IO b
241
showCmdCompletion personalities =
242
  putStr (multiCmdCompletion personalities) >> exitSuccess
243

    
244
-- | Command line parser, using a generic 'Options' structure.
245
parseOpts :: (StandardOptions a) =>
246
             a                      -- ^ The default options
247
          -> [String]               -- ^ The command line arguments
248
          -> String                 -- ^ The program name
249
          -> [GenericOptType a]     -- ^ The supported command line options
250
          -> [ArgCompletion]        -- ^ The supported command line arguments
251
          -> IO (a, [String])       -- ^ The resulting options and
252
                                    -- leftover arguments
253
parseOpts defaults argv progname options arguments =
254
  case parseOptsInner defaults argv progname options arguments of
255
    Left (code, msg) -> do
256
      hPutStr (if code == ExitSuccess then stdout else stderr) msg
257
      exitWith code
258
    Right result ->
259
      return result
260

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

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

    
322
-- | Parse command line options and execute the main function of a
323
-- multi-personality binary.
324
genericMainCmds :: (StandardOptions a) =>
325
                   a
326
                -> PersonalityList a
327
                -> [GenericOptType a]
328
                -> IO ()
329
genericMainCmds defaults personalities genopts = do
330
  cmd_args <- getArgs
331
  prog <- getProgName
332
  (opts, args, fn) <-
333
    parseOptsCmds defaults cmd_args prog personalities genopts
334
  fn opts args