On Sunday 18 January 2004 15:42, Tomasz Zielonka wrote: > [much explanation of his option processing approach elided]
Interesting technique - lots of cool ideas there. I too find getOpts to be a great base but have taken a different approach when writing console-mode Unix programs. Part of my approach is implemented (download http://www.cs.utah.edu/flux/knit/cmi.html for GPL'ed program and look in cmi/src/utils/FluxUtils/Prog.hs) and part is still in my head waiting for an excuse to go cleanup the code. Some of these tricks can be merged with Tomasz's technique (e.g., replace a call to writeFile with a call to writeOutput) while others are orthogonal (e.g., Tomasz deals with arguments one at a time whereas some of my tricks look for duplicated arguments or omitted arguments). I would be very interested in comments on this code, the Unix idioms they implement, Unix idioms omitted, applicability to Windows, MacOS, improving error messages, etc. Here's a list of common Unix idioms and how I implement them: 1) Interpreting the filename "-" as stdin or stdout I use this function (and a similar function for reading input). [Trivial detail: I use pretty printing for all I/O in my programs.] -- | -- Write to file ("-" means stdout) writeOutput :: FilePath -> Doc -> IO () writeOutput "-" output = do printDoc PageMode stdout output writeOutput outfile output = do h <- openFile outfile WriteMode printDoc PageMode h output hClose h 2) Treating arguments of the form 'VARNAME=VALUE' like environment variables (cf. GNU make) and 3) Printing usage info for malformed command lines type StringEnv = [(String,String)] -- | -- Split command line arguments into flags, variable bindings and other. compilerOpts :: (Show a, Eq a) => String -> [OptDescr a] -> IO ([a], StringEnv, [String]) compilerOpts usage options = do argv <- getArgs return $ case getOpt Permute options argv of (o,n,[]) -> (o, env, args) where (env, args) = getEnv n (_,_,errs) -> error (concat errs ++ usageInfo usage options) getEnv :: [String] -> (StringEnv,[String]) getEnv args = (map split env,rest) where (env, rest) = partition ('=' `elem`) args split x = (pre, tail post) where (pre,post) = break (== '=') x An alternative function is the following: -- | -- Extract command line arguments that are inside '+FOO' '-FOO' parentheses -- then split command line arguments into flags, variable bindings and other. -- This is usually used in preference to compilerOpts when a program has to -- (mostly) behave like another program - that is, when the options have to -- be somewhat hidden. runtimeOpts :: (Show a, Eq a) => String -> String -> String -> [OptDescr a] -> IO ([a], StringEnv, [String]) [Incidentally, a cleanup pass might well replace calls to 'error' with calls to one of the following functions: -- | -- Print an error message and exit program with a failure code failWith :: Doc -> IO a failWith msg = do printDoc PageMode stderr msg exitFailure -- | -- Print an error message and exit program with a failure code abortWith :: Doc -> a abortWith msg = unsafePerformIO (failWith (text "" $$ text "Error:" <+> msg)) ] 4) An option can be specified 0 or 1 times: Filter options using this function -- | -- Extract value from a list of length at most one. uniqueWithDefault :: String -> a -> [a] -> a uniqueWithDefault what d [] = d uniqueWithDefault what d [a] = a uniqueWithDefault what d _ = error $ "At most one " ++ what ++ " may be specified" For example, the CMI program starts off like this: -- src/cmi/CMI.hs main = do (flags,env,args) <- compilerOpts usage options let budget = uniqueWithDefault "-b" 0 [ i | Budget b <- flags, (i,"") <- reads b ] let outfile = uniqueWithDefault "-o" "flat.c" [ f | Outfile f <- flags ] let request_files = [ f | Requests f <- flags ] ... 5) An option must be specified exactly once: Filter options using this function: -- | -- Extract value from a list of length one. uniqueNoDefault :: String -> [a] -> a uniqueNoDefault what [] = error $ "You must specify " ++ what uniqueNoDefault what [a] = a uniqueNoDefault what _ = error $ "At most one " ++ what ++ " may be specified" For example, let outfile = uniqueNoDefault "-o" [ f | Outfile f <- flags ] 6) Implementing --help, --version, --numeric-version, --verbose Not implemented yet but I plan to handle these by having the 'compilerOpts' function implement these flags for me. That is, I would define: data StandardOptions = Help | Version | ... and 'compilerOpts' would add these options into the list it passes to getOpts. (The functions to add the options in and separate out the results are a little tedious but not hard.) I'm pretty much agnostic about whether the strings for version, numeric-version, help, etc. should be provided as individual arguments or as a Haskell record. 7) --verbose output and varying levels of verbosity I generate all informational output using this function where the first argument is either True (generate output) or False (don't generate output). -- | -- Print message to stderr if condition holds blurt :: Bool -> Doc -> IO () blurt False msg = return () blurt True msg = printDoc PageMode stderr msg The first argument is usually based on the --verbose flag which is initialized by code like this: let verbosity = length (filter (==Verbose) flags) and a typical call looks like this: blurt (verbosity > 4) $ text "Stripped input:" <+> vmap pp cs [This could probably be improved on using one of a variety of ways of distributing command line flags around a program.] -- Alastair Reid www.haskell-consulting.com _______________________________________________ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell