| Portability | portable | 
|---|---|
| Stability | experimental | 
| Maintainer | libraries@haskell.org | 
| Safe Haskell | Safe | 
System.Console.GetOpt
Contents
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.
- getOpt :: ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String])
- getOpt' :: ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String], [String])
- usageInfo :: String -> [OptDescr a] -> String
- data  ArgOrder a- = RequireOrder
- | Permute
- | ReturnInOrder (String -> a)
 
- data OptDescr a = Option [Char] [String] (ArgDescr a) String
- data ArgDescr a
GetOpt
getOpt :: ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String])Source
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 option arguments, a list
of non-options, and a list of error messages.
getOpt' :: ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String], [String])Source
This is almost the same as getOpt, but returns a quadruple
consisting of the option arguments, a list of non-options, a list of
unrecognized options, and a list of error messages.
usageInfo :: String -> [OptDescr a] -> StringSource
Return a string describing the usage of a command, derived from the header (first argument) and the options described by the second argument.
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 | 
Describes whether an option takes an argument or not, and if so
 how the argument is injected into a value of type a.
Examples
To hopefully illuminate the role of the different data structures,
 here are the command-line options for a (very simple) compiler,
 done in two different ways.
 The difference arises because the type of getOpt is
 parameterized by the type of values derived from flags.
Interpreting flags as concrete values
A simple choice for the type associated with flags is to define a type
Flag as an algebraic type representing the possible flags and their
arguments:
    module Opts1 where
    
    import System.Console.GetOpt
    import Data.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 "stdin"
    
    compilerOpts :: [String] -> IO ([Flag], [String])
    compilerOpts argv = 
       case getOpt Permute options argv of
          (o,n,[]  ) -> return (o,n)
          (_,_,errs) -> ioError (userError (concat errs ++ usageInfo header options))
      where header = "Usage: ic [OPTION...] files..."
Then the rest of the program will use the constructed list of flags to determine it's behaviour.
Interpreting flags as transformations of an options record
A different approach is to group the option values in a record of type
Options, and have each flag yield a function of type
Options -> Options transforming this record.
    module Opts2 where
    import System.Console.GetOpt
    import Data.Maybe ( fromMaybe )
    data Options = Options
     { optVerbose     :: Bool
     , optShowVersion :: Bool
     , optOutput      :: Maybe FilePath
     , optInput       :: Maybe FilePath
     , optLibDirs     :: [FilePath]
     } deriving Show
    defaultOptions    = Options
     { optVerbose     = False
     , optShowVersion = False
     , optOutput      = Nothing
     , optInput       = Nothing
     , optLibDirs     = []
     }
    options :: [OptDescr (Options -> Options)]
    options =
     [ Option ['v']     ["verbose"]
         (NoArg (\ opts -> opts { optVerbose = True }))
         "chatty output on stderr"
     , Option ['V','?'] ["version"]
         (NoArg (\ opts -> opts { optShowVersion = True }))
         "show version number"
     , Option ['o']     ["output"]
         (OptArg ((\ f opts -> opts { optOutput = Just f }) . fromMaybe "output")
                 "FILE")
         "output FILE"
     , Option ['c']     []
         (OptArg ((\ f opts -> opts { optInput = Just f }) . fromMaybe "input")
                 "FILE")
         "input FILE"
     , Option ['L']     ["libdir"]
         (ReqArg (\ d opts -> opts { optLibDirs = optLibDirs opts ++ [d] }) "DIR")
         "library directory"
     ]
    compilerOpts :: [String] -> IO (Options, [String])
    compilerOpts argv =
       case getOpt Permute options argv of
          (o,n,[]  ) -> return (foldl (flip id) defaultOptions o, n)
          (_,_,errs) -> ioError (userError (concat errs ++ usageInfo header options))
      where header = "Usage: ic [OPTION...] files..."
Similarly, each flag could yield a monadic function transforming a record,
of type Options -> IO Options (or any other monad), allowing option
processing to perform actions of the chosen monad, e.g. printing help or
version messages, checking that file arguments exist, etc.