Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / Common.hs @ 0ea11dcb

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