add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / System / Console / GetOpt.hs
1 -----------------------------------------------------------------------------
2 -- |
3 -- Module      :  System.Console.GetOpt
4 -- Copyright   :  (c) Sven Panne 2002-2005
5 -- License     :  BSD-style (see the file libraries/base/LICENSE)
6 -- 
7 -- Maintainer  :  libraries@haskell.org
8 -- Stability   :  experimental
9 -- Portability :  portable
10 --
11 -- This library provides facilities for parsing the command-line options
12 -- in a standalone program.  It is essentially a Haskell port of the GNU 
13 -- @getopt@ library.
14 --
15 -----------------------------------------------------------------------------
16
17 {-
18 Sven Panne <Sven.Panne@informatik.uni-muenchen.de> Oct. 1996 (small
19 changes Dec. 1997)
20
21 Two rather obscure features are missing: The Bash 2.0 non-option hack
22 (if you don't already know it, you probably don't want to hear about
23 it...) and the recognition of long options with a single dash
24 (e.g. '-help' is recognised as '--help', as long as there is no short
25 option 'h').
26
27 Other differences between GNU's getopt and this implementation:
28
29 * To enforce a coherent description of options and arguments, there
30   are explanation fields in the option/argument descriptor.
31
32 * Error messages are now more informative, but no longer POSIX
33   compliant... :-(
34
35 And a final Haskell advertisement: The GNU C implementation uses well
36 over 1100 lines, we need only 195 here, including a 46 line example! 
37 :-)
38 -}
39
40 module System.Console.GetOpt (
41    -- * GetOpt
42    getOpt, getOpt',
43    usageInfo,
44    ArgOrder(..),
45    OptDescr(..),
46    ArgDescr(..),
47
48    -- * Examples
49
50    -- |To hopefully illuminate the role of the different data structures,
51    -- here are the command-line options for a (very simple) compiler,
52    -- done in two different ways.
53    -- The difference arises because the type of 'getOpt' is
54    -- parameterized by the type of values derived from flags.
55
56    -- ** Interpreting flags as concrete values
57    -- $example1
58
59    -- ** Interpreting flags as transformations of an options record
60    -- $example2
61 ) where
62
63 import Prelude -- necessary to get dependencies right
64
65 import Data.List ( isPrefixOf, find )
66
67 -- |What to do with options following non-options
68 data ArgOrder a
69   = RequireOrder                -- ^ no option processing after first non-option
70   | Permute                     -- ^ freely intersperse options and non-options
71   | ReturnInOrder (String -> a) -- ^ wrap non-options into options
72
73 {-|
74 Each 'OptDescr' describes a single option.
75
76 The arguments to 'Option' are:
77
78 * list of short option characters
79
80 * list of long option strings (without \"--\")
81
82 * argument descriptor
83
84 * explanation of option for user
85 -}
86 data OptDescr a =              -- description of a single options:
87    Option [Char]                --    list of short option characters
88           [String]              --    list of long option strings (without "--")
89           (ArgDescr a)          --    argument descriptor
90           String                --    explanation of option for user
91
92 -- |Describes whether an option takes an argument or not, and if so
93 -- how the argument is injected into a value of type @a@.
94 data ArgDescr a
95    = NoArg                   a         -- ^   no argument expected
96    | ReqArg (String       -> a) String -- ^   option requires argument
97    | OptArg (Maybe String -> a) String -- ^   optional argument
98
99 data OptKind a                -- kind of cmd line arg (internal use only):
100    = Opt       a                --    an option
101    | UnreqOpt  String           --    an un-recognized option
102    | NonOpt    String           --    a non-option
103    | EndOfOpts                  --    end-of-options marker (i.e. "--")
104    | OptErr    String           --    something went wrong...
105
106 -- | Return a string describing the usage of a command, derived from
107 -- the header (first argument) and the options described by the 
108 -- second argument.
109 usageInfo :: String                    -- header
110           -> [OptDescr a]              -- option descriptors
111           -> String                    -- nicely formatted decription of options
112 usageInfo header optDescr = unlines (header:table)
113    where (ss,ls,ds)     = (unzip3 . concatMap fmtOpt) optDescr
114          table          = zipWith3 paste (sameLen ss) (sameLen ls) ds
115          paste x y z    = "  " ++ x ++ "  " ++ y ++ "  " ++ z
116          sameLen xs     = flushLeft ((maximum . map length) xs) xs
117          flushLeft n xs = [ take n (x ++ repeat ' ') | x <- xs ]
118
119 fmtOpt :: OptDescr a -> [(String,String,String)]
120 fmtOpt (Option sos los ad descr) =
121    case lines descr of
122      []     -> [(sosFmt,losFmt,"")]
123      (d:ds) ->  (sosFmt,losFmt,d) : [ ("","",d') | d' <- ds ]
124    where sepBy _  []     = ""
125          sepBy _  [x]    = x
126          sepBy ch (x:xs) = x ++ ch:' ':sepBy ch xs
127          sosFmt = sepBy ',' (map (fmtShort ad) sos)
128          losFmt = sepBy ',' (map (fmtLong  ad) los)
129
130 fmtShort :: ArgDescr a -> Char -> String
131 fmtShort (NoArg  _   ) so = "-" ++ [so]
132 fmtShort (ReqArg _ ad) so = "-" ++ [so] ++ " " ++ ad
133 fmtShort (OptArg _ ad) so = "-" ++ [so] ++ "[" ++ ad ++ "]"
134
135 fmtLong :: ArgDescr a -> String -> String
136 fmtLong (NoArg  _   ) lo = "--" ++ lo
137 fmtLong (ReqArg _ ad) lo = "--" ++ lo ++ "=" ++ ad
138 fmtLong (OptArg _ ad) lo = "--" ++ lo ++ "[=" ++ ad ++ "]"
139
140 {-|
141 Process the command-line, and return the list of values that matched
142 (and those that didn\'t). The arguments are:
143
144 * The order requirements (see 'ArgOrder')
145
146 * The option descriptions (see 'OptDescr')
147
148 * The actual command line arguments (presumably got from 
149   'System.Environment.getArgs').
150
151 'getOpt' returns a triple consisting of the option arguments, a list
152 of non-options, and a list of error messages.
153 -}
154 getOpt :: ArgOrder a                   -- non-option handling
155        -> [OptDescr a]                 -- option descriptors
156        -> [String]                     -- the command-line arguments
157        -> ([a],[String],[String])      -- (options,non-options,error messages)
158 getOpt ordering optDescr args = (os,xs,es ++ map errUnrec us)
159    where (os,xs,us,es) = getOpt' ordering optDescr args
160
161 {-|
162 This is almost the same as 'getOpt', but returns a quadruple
163 consisting of the option arguments, a list of non-options, a list of
164 unrecognized options, and a list of error messages.
165 -}
166 getOpt' :: ArgOrder a                         -- non-option handling
167         -> [OptDescr a]                       -- option descriptors
168         -> [String]                           -- the command-line arguments
169         -> ([a],[String], [String] ,[String]) -- (options,non-options,unrecognized,error messages)
170 getOpt' _        _        []         =  ([],[],[],[])
171 getOpt' ordering optDescr (arg:args) = procNextOpt opt ordering
172    where procNextOpt (Opt o)      _                 = (o:os,xs,us,es)
173          procNextOpt (UnreqOpt u) _                 = (os,xs,u:us,es)
174          procNextOpt (NonOpt x)   RequireOrder      = ([],x:rest,[],[])
175          procNextOpt (NonOpt x)   Permute           = (os,x:xs,us,es)
176          procNextOpt (NonOpt x)   (ReturnInOrder f) = (f x :os, xs,us,es)
177          procNextOpt EndOfOpts    RequireOrder      = ([],rest,[],[])
178          procNextOpt EndOfOpts    Permute           = ([],rest,[],[])
179          procNextOpt EndOfOpts    (ReturnInOrder f) = (map f rest,[],[],[])
180          procNextOpt (OptErr e)   _                 = (os,xs,us,e:es)
181
182          (opt,rest) = getNext arg args optDescr
183          (os,xs,us,es) = getOpt' ordering optDescr rest
184
185 -- take a look at the next cmd line arg and decide what to do with it
186 getNext :: String -> [String] -> [OptDescr a] -> (OptKind a,[String])
187 getNext ('-':'-':[]) rest _        = (EndOfOpts,rest)
188 getNext ('-':'-':xs) rest optDescr = longOpt xs rest optDescr
189 getNext ('-': x :xs) rest optDescr = shortOpt x xs rest optDescr
190 getNext a            rest _        = (NonOpt a,rest)
191
192 -- handle long option
193 longOpt :: String -> [String] -> [OptDescr a] -> (OptKind a,[String])
194 longOpt ls rs optDescr = long ads arg rs
195    where (opt,arg) = break (=='=') ls
196          getWith p = [ o | o@(Option _ xs _ _) <- optDescr
197                          , find (p opt) xs /= Nothing ]
198          exact     = getWith (==)
199          options   = if null exact then getWith isPrefixOf else exact
200          ads       = [ ad | Option _ _ ad _ <- options ]
201          optStr    = ("--"++opt)
202
203          long (_:_:_)      _        rest     = (errAmbig options optStr,rest)
204          long [NoArg  a  ] []       rest     = (Opt a,rest)
205          long [NoArg  _  ] ('=':_)  rest     = (errNoArg optStr,rest)
206          long [ReqArg _ d] []       []       = (errReq d optStr,[])
207          long [ReqArg f _] []       (r:rest) = (Opt (f r),rest)
208          long [ReqArg f _] ('=':xs) rest     = (Opt (f xs),rest)
209          long [OptArg f _] []       rest     = (Opt (f Nothing),rest)
210          long [OptArg f _] ('=':xs) rest     = (Opt (f (Just xs)),rest)
211          long _            _        rest     = (UnreqOpt ("--"++ls),rest)
212
213 -- handle short option
214 shortOpt :: Char -> String -> [String] -> [OptDescr a] -> (OptKind a,[String])
215 shortOpt y ys rs optDescr = short ads ys rs
216   where options = [ o  | o@(Option ss _ _ _) <- optDescr, s <- ss, y == s ]
217         ads     = [ ad | Option _ _ ad _ <- options ]
218         optStr  = '-':[y]
219
220         short (_:_:_)        _  rest     = (errAmbig options optStr,rest)
221         short (NoArg  a  :_) [] rest     = (Opt a,rest)
222         short (NoArg  a  :_) xs rest     = (Opt a,('-':xs):rest)
223         short (ReqArg _ d:_) [] []       = (errReq d optStr,[])
224         short (ReqArg f _:_) [] (r:rest) = (Opt (f r),rest)
225         short (ReqArg f _:_) xs rest     = (Opt (f xs),rest)
226         short (OptArg f _:_) [] rest     = (Opt (f Nothing),rest)
227         short (OptArg f _:_) xs rest     = (Opt (f (Just xs)),rest)
228         short []             [] rest     = (UnreqOpt optStr,rest)
229         short []             xs rest     = (UnreqOpt optStr,('-':xs):rest)
230
231 -- miscellaneous error formatting
232
233 errAmbig :: [OptDescr a] -> String -> OptKind a
234 errAmbig ods optStr = OptErr (usageInfo header ods)
235    where header = "option `" ++ optStr ++ "' is ambiguous; could be one of:"
236
237 errReq :: String -> String -> OptKind a
238 errReq d optStr = OptErr ("option `" ++ optStr ++ "' requires an argument " ++ d ++ "\n")
239
240 errUnrec :: String -> String
241 errUnrec optStr = "unrecognized option `" ++ optStr ++ "'\n"
242
243 errNoArg :: String -> OptKind a
244 errNoArg optStr = OptErr ("option `" ++ optStr ++ "' doesn't allow an argument\n")
245
246 {-
247 -----------------------------------------------------------------------------------------
248 -- and here a small and hopefully enlightening example:
249
250 data Flag = Verbose | Version | Name String | Output String | Arg String   deriving Show
251
252 options :: [OptDescr Flag]
253 options =
254    [Option ['v']     ["verbose"]           (NoArg Verbose)      "verbosely list files",
255     Option ['V','?'] ["version","release"] (NoArg Version)      "show version info",
256     Option ['o']     ["output"]            (OptArg out "FILE")  "use FILE for dump",
257     Option ['n']     ["name"]              (ReqArg Name "USER") "only dump USER's files"]
258
259 out :: Maybe String -> Flag
260 out Nothing  = Output "stdout"
261 out (Just o) = Output o
262
263 test :: ArgOrder Flag -> [String] -> String
264 test order cmdline = case getOpt order options cmdline of
265                         (o,n,[]  ) -> "options=" ++ show o ++ "  args=" ++ show n ++ "\n"
266                         (_,_,errs) -> concat errs ++ usageInfo header options
267    where header = "Usage: foobar [OPTION...] files..."
268
269 -- example runs:
270 -- putStr (test RequireOrder ["foo","-v"])
271 --    ==> options=[]  args=["foo", "-v"]
272 -- putStr (test Permute ["foo","-v"])
273 --    ==> options=[Verbose]  args=["foo"]
274 -- putStr (test (ReturnInOrder Arg) ["foo","-v"])
275 --    ==> options=[Arg "foo", Verbose]  args=[]
276 -- putStr (test Permute ["foo","--","-v"])
277 --    ==> options=[]  args=["foo", "-v"]
278 -- putStr (test Permute ["-?o","--name","bar","--na=baz"])
279 --    ==> options=[Version, Output "stdout", Name "bar", Name "baz"]  args=[]
280 -- putStr (test Permute ["--ver","foo"])
281 --    ==> option `--ver' is ambiguous; could be one of:
282 --          -v      --verbose             verbosely list files
283 --          -V, -?  --version, --release  show version info   
284 --        Usage: foobar [OPTION...] files...
285 --          -v        --verbose             verbosely list files  
286 --          -V, -?    --version, --release  show version info     
287 --          -o[FILE]  --output[=FILE]       use FILE for dump     
288 --          -n USER   --name=USER           only dump USER's files
289 -----------------------------------------------------------------------------------------
290 -}
291
292 {- $example1
293
294 A simple choice for the type associated with flags is to define a type
295 @Flag@ as an algebraic type representing the possible flags and their
296 arguments:
297
298 >    module Opts1 where
299 >    
300 >    import System.Console.GetOpt
301 >    import Data.Maybe ( fromMaybe )
302 >    
303 >    data Flag 
304 >     = Verbose  | Version 
305 >     | Input String | Output String | LibDir String
306 >       deriving Show
307 >    
308 >    options :: [OptDescr Flag]
309 >    options =
310 >     [ Option ['v']     ["verbose"] (NoArg Verbose)       "chatty output on stderr"
311 >     , Option ['V','?'] ["version"] (NoArg Version)       "show version number"
312 >     , Option ['o']     ["output"]  (OptArg outp "FILE")  "output FILE"
313 >     , Option ['c']     []          (OptArg inp  "FILE")  "input FILE"
314 >     , Option ['L']     ["libdir"]  (ReqArg LibDir "DIR") "library directory"
315 >     ]
316 >    
317 >    inp,outp :: Maybe String -> Flag
318 >    outp = Output . fromMaybe "stdout"
319 >    inp  = Input  . fromMaybe "stdin"
320 >    
321 >    compilerOpts :: [String] -> IO ([Flag], [String])
322 >    compilerOpts argv = 
323 >       case getOpt Permute options argv of
324 >          (o,n,[]  ) -> return (o,n)
325 >          (_,_,errs) -> ioError (userError (concat errs ++ usageInfo header options))
326 >      where header = "Usage: ic [OPTION...] files..."
327
328 Then the rest of the program will use the constructed list of flags
329 to determine it\'s behaviour.
330
331 -}
332
333 {- $example2
334
335 A different approach is to group the option values in a record of type
336 @Options@, and have each flag yield a function of type
337 @Options -> Options@ transforming this record.
338
339 >    module Opts2 where
340 >
341 >    import System.Console.GetOpt
342 >    import Data.Maybe ( fromMaybe )
343 >
344 >    data Options = Options
345 >     { optVerbose     :: Bool
346 >     , optShowVersion :: Bool
347 >     , optOutput      :: Maybe FilePath
348 >     , optInput       :: Maybe FilePath
349 >     , optLibDirs     :: [FilePath]
350 >     } deriving Show
351 >
352 >    defaultOptions    = Options
353 >     { optVerbose     = False
354 >     , optShowVersion = False
355 >     , optOutput      = Nothing
356 >     , optInput       = Nothing
357 >     , optLibDirs     = []
358 >     }
359 >
360 >    options :: [OptDescr (Options -> Options)]
361 >    options =
362 >     [ Option ['v']     ["verbose"]
363 >         (NoArg (\ opts -> opts { optVerbose = True }))
364 >         "chatty output on stderr"
365 >     , Option ['V','?'] ["version"]
366 >         (NoArg (\ opts -> opts { optShowVersion = True }))
367 >         "show version number"
368 >     , Option ['o']     ["output"]
369 >         (OptArg ((\ f opts -> opts { optOutput = Just f }) . fromMaybe "output")
370 >                 "FILE")
371 >         "output FILE"
372 >     , Option ['c']     []
373 >         (OptArg ((\ f opts -> opts { optInput = Just f }) . fromMaybe "input")
374 >                 "FILE")
375 >         "input FILE"
376 >     , Option ['L']     ["libdir"]
377 >         (ReqArg (\ d opts -> opts { optLibDirs = optLibDirs opts ++ [d] }) "DIR")
378 >         "library directory"
379 >     ]
380 >
381 >    compilerOpts :: [String] -> IO (Options, [String])
382 >    compilerOpts argv =
383 >       case getOpt Permute options argv of
384 >          (o,n,[]  ) -> return (foldl (flip id) defaultOptions o, n)
385 >          (_,_,errs) -> ioError (userError (concat errs ++ usageInfo header options))
386 >      where header = "Usage: ic [OPTION...] files..."
387
388 Similarly, each flag could yield a monadic function transforming a record,
389 of type @Options -> IO Options@ (or any other monad), allowing option
390 processing to perform actions of the chosen monad, e.g. printing help or
391 version messages, checking that file arguments exist, etc.
392
393 -}