The GetOpt library contains Sven Panne's Haskell implementation of getopt, providing features nigh-on identical to GNU getopt:
module GetOpt where -- representing a single option: data OptDescr a = Option [Char] -- list of short option characters [String] -- list of long option strings (without "--") (ArgDescr a) -- argument descriptor String -- explanation of option for user -- argument option: data ArgDescr a = NoArg a -- no argument expected | ReqArg (String -> a) String -- option requires argument | OptArg (Maybe String -> a) String -- optional argument usageInfo :: String -- header -> [OptDescr a] -- options recognised -> String -- nicely formatted decription of options getOpt :: ArgOrder a -- non-option handling -> [OptDescr a] -- options recognised -> [String] -- the command-line -> ( [a] -- options , [String] -- non-options ,[String] -- error messages ) data ArgOrder a = RequireOrder | Permute | ReturnInOrder (String -> a) |
The command-line options recognised is described by a list of OptDescr values. The OptDescr describes the long and short strings that recognise the option, together with a help string and info on whether the option takes extra arguments, if any.
From a list of option values, usageInfo returns a nicely formatted string that enumerates the different options supported together with a short message about what
To decode a command-line with respect to a list of options, getOpt is used. It processes the command-line, and returns the list of values that matched (and those that didn't). The first argument to getOpt controls whether the user is to give the options in any old order or not.
To hopefully illuminate the role of the different GetOpt data structures, here's the command-line options for a (very simple) compiler:
module Opts where import GetOpt import Maybe ( fromMaybe ) data Flag = Verbose | Version | Input String | Output String | LibDir String deriving Show options :: [OptDescr Flag] options = [ Option ['v'] ["verbose"] (NoArg Verbose) "chatty output on stderr" , Option ['V','?'] ["version"] (NoArg Version) "show version number" , Option ['o'] ["output"] (OptArg outp "FILE") "output FILE" , Option ['c'] [] (OptArg inp "FILE") "input FILE" , Option ['L'] ["libdir"] (ReqArg LibDir "DIR") "library directory" ] inp,outp :: Maybe String -> Flag outp = Output . fromMaybe "stdout" inp = Input . fromMaybe "stdout" compilerOpts :: [String] -> IO ([Flag], [String]) compilerOpts argv = case (getOpt Permute options argv) of (o,n,[] ) -> return (o,n) (_,_,errs) -> fail (userError (concat errs ++ usageInfo header options)) where header = "Usage: ic [OPTION...] files..." |