|
System.Console.GetOpt | Portability | portable | Stability | experimental | Maintainer | libraries@haskell.org |
|
|
|
|
Contents |
- GetOpt
- Example
|
|
Description |
This library provides facilities for parsing the command-line options
in a standalone program. It is essentially a Haskell port of the GNU
getopt library.
|
|
Synopsis |
|
|
|
|
GetOpt |
|
getOpt :: ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String]) |
Process the command-line, and return the list of values that matched
(and those that didn't). The arguments are: The order requirements (see ArgOrder) The option descriptions (see OptDescr) The actual command line arguments (presumably got from
getArgs).
getOpt returns a triple, consisting of the argument values, a list
of options that didn't match, and a list of error messages.
|
|
usageInfo :: String -> [OptDescr a] -> String |
Return a string describing the usage of a command, derived from
the header (first argument) and the options described by the
second argument. |
|
data ArgOrder a |
What to do with options following non-options | Constructors | RequireOrder | no option processing after first non-option | Permute | freely intersperse options and non-options | ReturnInOrder (String -> a) | wrap non-options into options |
|
|
|
data OptDescr a |
Each OptDescr describes a single option. The arguments to Option are: list of short option characters list of long option strings (without --) argument descriptor explanation of option for user
| Constructors | |
|
|
data ArgDescr a |
Describes whether an option takes an argument or not, and if so
how the argument is injected into a value of type a. | Constructors | |
|
|
Example |
|
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) -> failIO (concat errs ++ usageInfo header options)
where header = "Usage: ic [OPTION...] files..." |
|
Produced by Haddock version 0.4 |