[project @ 2005-01-23 13:12:52 by panne]
[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,
43    usageInfo,
44    ArgOrder(..),
45    OptDescr(..),
46    ArgDescr(..),
47
48    -- * Example
49
50    -- $example
51 ) where
52
53 import Prelude -- necessary to get dependencies right
54
55 import Data.List ( isPrefixOf )
56
57 -- |What to do with options following non-options
58 data ArgOrder a
59   = RequireOrder                -- ^ no option processing after first non-option
60   | Permute                     -- ^ freely intersperse options and non-options
61   | ReturnInOrder (String -> a) -- ^ wrap non-options into options
62
63 {-|
64 Each 'OptDescr' describes a single option.
65
66 The arguments to 'Option' are:
67
68 * list of short option characters
69
70 * list of long option strings (without \"--\")
71
72 * argument descriptor
73
74 * explanation of option for user
75 -}
76 data OptDescr a =              -- description of a single options:
77    Option [Char]                --    list of short option characters
78           [String]              --    list of long option strings (without "--")
79           (ArgDescr a)          --    argument descriptor
80           String                --    explanation of option for user
81
82 -- |Describes whether an option takes an argument or not, and if so
83 -- how the argument is injected into a value of type @a@.
84 data ArgDescr a
85    = NoArg                   a         -- ^   no argument expected
86    | ReqArg (String       -> a) String -- ^   option requires argument
87    | OptArg (Maybe String -> a) String -- ^   optional argument
88
89 data OptKind a                -- kind of cmd line arg (internal use only):
90    = Opt       a                --    an option
91    | UnreqOpt  String           --    an un-recognized option
92    | NonOpt    String           --    a non-option
93    | EndOfOpts                  --    end-of-options marker (i.e. "--")
94    | OptErr    String           --    something went wrong...
95
96 -- | Return a string describing the usage of a command, derived from
97 -- the header (first argument) and the options described by the 
98 -- second argument.
99 usageInfo :: String                    -- header
100           -> [OptDescr a]              -- option descriptors
101           -> String                    -- nicely formatted decription of options
102 usageInfo header optDescr = unlines (header:table)
103    where (ss,ls,ds)     = (unzip3 . concatMap fmtOpt) optDescr
104          table          = zipWith3 paste (sameLen ss) (sameLen ls) ds
105          paste x y z    = "  " ++ x ++ "  " ++ y ++ "  " ++ z
106          sameLen xs     = flushLeft ((maximum . map length) xs) xs
107          flushLeft n xs = [ take n (x ++ repeat ' ') | x <- xs ]
108
109 fmtOpt :: OptDescr a -> [(String,String,String)]
110 fmtOpt (Option sos los ad descr) =
111    case lines descr of
112      []     -> [(sosFmt,losFmt,"")]
113      (d:ds) ->  (sosFmt,losFmt,d) : [ ("","",d') | d' <- ds ]
114    where sepBy _  []     = ""
115          sepBy _  [x]    = x
116          sepBy ch (x:xs) = x ++ ch:' ':sepBy ch xs
117          sosFmt = sepBy ',' (map (fmtShort ad) sos)
118          losFmt = sepBy ',' (map (fmtLong  ad) los)
119
120 fmtShort :: ArgDescr a -> Char -> String
121 fmtShort (NoArg  _   ) so = "-" ++ [so]
122 fmtShort (ReqArg _ ad) so = "-" ++ [so] ++ " " ++ ad
123 fmtShort (OptArg _ ad) so = "-" ++ [so] ++ "[" ++ ad ++ "]"
124
125 fmtLong :: ArgDescr a -> String -> String
126 fmtLong (NoArg  _   ) lo = "--" ++ lo
127 fmtLong (ReqArg _ ad) lo = "--" ++ lo ++ "=" ++ ad
128 fmtLong (OptArg _ ad) lo = "--" ++ lo ++ "[=" ++ ad ++ "]"
129
130 {-|
131 Process the command-line, and return the list of values that matched
132 (and those that didn\'t). The arguments are:
133
134 * The order requirements (see 'ArgOrder')
135
136 * The option descriptions (see 'OptDescr')
137
138 * The actual command line arguments (presumably got from 
139   'System.Environment.getArgs').
140
141 'getOpt' returns a triple, consisting of the argument values, a list
142 of options that didn\'t match, and a list of error messages.
143 -}
144 getOpt :: ArgOrder a                   -- non-option handling
145        -> [OptDescr a]                 -- option descriptors
146        -> [String]                     -- the commandline arguments
147        -> ([a],[String],[String])      -- (options,non-options,error messages)
148 getOpt _        _        []         =  ([],[],[])
149 getOpt ordering optDescr (arg:args) = procNextOpt opt ordering
150    where procNextOpt (Opt o)    _                 = (o:os,xs,es)
151          procNextOpt (NonOpt x) RequireOrder      = ([],x:rest,[])
152          procNextOpt (NonOpt x) Permute           = (os,x:xs,es)
153          procNextOpt (NonOpt x) (ReturnInOrder f) = (f x :os, xs,es)
154          procNextOpt EndOfOpts  RequireOrder      = ([],rest,[])
155          procNextOpt EndOfOpts  Permute           = ([],rest,[])
156          procNextOpt EndOfOpts  (ReturnInOrder f) = (map f rest,[],[])
157          procNextOpt (OptErr e) _                 = (os,xs,e:es)
158          procNextOpt (UnreqOpt _) _               = error "should not happen"
159
160          (opt,rest) = getNext arg args optDescr
161          (os,xs,es) = getOpt ordering optDescr rest
162
163 -- take a look at the next cmd line arg and decide what to do with it
164 getNext :: String -> [String] -> [OptDescr a] -> (OptKind a,[String])
165 getNext ('-':'-':[]) rest _        = (EndOfOpts,rest)
166 getNext ('-':'-':xs) rest optDescr = longOpt xs rest optDescr
167 getNext ('-': x :xs) rest optDescr = shortOpt x xs rest optDescr
168 getNext a            rest _        = (NonOpt a,rest)
169
170 -- handle long option
171 longOpt :: String -> [String] -> [OptDescr a] -> (OptKind a,[String])
172 longOpt ls rs optDescr = long ads arg rs
173    where (opt,arg) = break (=='=') ls
174          getWith p = [ o  | o@(Option _ xs _ _) <- optDescr, x <- xs, opt `p` x ]
175          exact     = getWith (==)
176          options   = if null exact then getWith isPrefixOf else exact
177          ads       = [ ad | Option _ _ ad _ <- options ]
178          optStr    = ("--"++opt)
179
180          long (_:_:_)      _        rest     = (errAmbig options optStr,rest)
181          long [NoArg  a  ] []       rest     = (Opt a,rest)
182          long [NoArg  _  ] ('=':_)  rest     = (errNoArg optStr,rest)
183          long [ReqArg _ d] []       []       = (errReq d optStr,[])
184          long [ReqArg f _] []       (r:rest) = (Opt (f r),rest)
185          long [ReqArg f _] ('=':xs) rest     = (Opt (f xs),rest)
186          long [OptArg f _] []       rest     = (Opt (f Nothing),rest)
187          long [OptArg f _] ('=':xs) rest     = (Opt (f (Just xs)),rest)
188          long _            _        rest     = (errUnrec optStr,rest)
189
190 -- handle short option
191 shortOpt :: Char -> String -> [String] -> [OptDescr a] -> (OptKind a,[String])
192 shortOpt y ys rs optDescr = short ads ys rs
193   where options = [ o  | o@(Option ss _ _ _) <- optDescr, s <- ss, y == s ]
194         ads     = [ ad | Option _ _ ad _ <- options ]
195         optStr  = '-':[y]
196
197         short (_:_:_)        _  rest     = (errAmbig options optStr,rest)
198         short (NoArg  a  :_) [] rest     = (Opt a,rest)
199         short (NoArg  a  :_) xs rest     = (Opt a,('-':xs):rest)
200         short (ReqArg _ d:_) [] []       = (errReq d optStr,[])
201         short (ReqArg f _:_) [] (r:rest) = (Opt (f r),rest)
202         short (ReqArg f _:_) xs rest     = (Opt (f xs),rest)
203         short (OptArg f _:_) [] rest     = (Opt (f Nothing),rest)
204         short (OptArg f _:_) xs rest     = (Opt (f (Just xs)),rest)
205         short []             [] rest     = (errUnrec optStr,rest)
206         short []             xs rest     = (errUnrec optStr,('-':xs):rest)
207
208 -- miscellaneous error formatting
209
210 errAmbig :: [OptDescr a] -> String -> OptKind a
211 errAmbig ods optStr = OptErr (usageInfo header ods)
212    where header = "option `" ++ optStr ++ "' is ambiguous; could be one of:"
213
214 errReq :: String -> String -> OptKind a
215 errReq d optStr = OptErr ("option `" ++ optStr ++ "' requires an argument " ++ d ++ "\n")
216
217 errUnrec :: String -> OptKind a
218 errUnrec optStr = OptErr ("unrecognized option `" ++ optStr ++ "'\n")
219
220 errNoArg :: String -> OptKind a
221 errNoArg optStr = OptErr ("option `" ++ optStr ++ "' doesn't allow an argument\n")
222
223 {-
224 -----------------------------------------------------------------------------------------
225 -- and here a small and hopefully enlightening example:
226
227 data Flag = Verbose | Version | Name String | Output String | Arg String   deriving Show
228
229 options :: [OptDescr Flag]
230 options =
231    [Option ['v']     ["verbose"]           (NoArg Verbose)      "verbosely list files",
232     Option ['V','?'] ["version","release"] (NoArg Version)      "show version info",
233     Option ['o']     ["output"]            (OptArg out "FILE")  "use FILE for dump",
234     Option ['n']     ["name"]              (ReqArg Name "USER") "only dump USER's files"]
235
236 out :: Maybe String -> Flag
237 out Nothing  = Output "stdout"
238 out (Just o) = Output o
239
240 test :: ArgOrder Flag -> [String] -> String
241 test order cmdline = case getOpt order options cmdline of
242                         (o,n,[]  ) -> "options=" ++ show o ++ "  args=" ++ show n ++ "\n"
243                         (_,_,errs) -> concat errs ++ usageInfo header options
244    where header = "Usage: foobar [OPTION...] files..."
245
246 -- example runs:
247 -- putStr (test RequireOrder ["foo","-v"])
248 --    ==> options=[]  args=["foo", "-v"]
249 -- putStr (test Permute ["foo","-v"])
250 --    ==> options=[Verbose]  args=["foo"]
251 -- putStr (test (ReturnInOrder Arg) ["foo","-v"])
252 --    ==> options=[Arg "foo", Verbose]  args=[]
253 -- putStr (test Permute ["foo","--","-v"])
254 --    ==> options=[]  args=["foo", "-v"]
255 -- putStr (test Permute ["-?o","--name","bar","--na=baz"])
256 --    ==> options=[Version, Output "stdout", Name "bar", Name "baz"]  args=[]
257 -- putStr (test Permute ["--ver","foo"])
258 --    ==> option `--ver' is ambiguous; could be one of:
259 --          -v      --verbose             verbosely list files
260 --          -V, -?  --version, --release  show version info   
261 --        Usage: foobar [OPTION...] files...
262 --          -v        --verbose             verbosely list files  
263 --          -V, -?    --version, --release  show version info     
264 --          -o[FILE]  --output[=FILE]       use FILE for dump     
265 --          -n USER   --name=USER           only dump USER's files
266 -----------------------------------------------------------------------------------------
267 -}
268
269 {- $example
270
271 To hopefully illuminate the role of the different data
272 structures, here\'s the command-line options for a (very simple)
273 compiler:
274
275 >    module Opts where
276 >    
277 >    import System.Console.GetOpt
278 >    import Data.Maybe ( fromMaybe )
279 >    
280 >    data Flag 
281 >     = Verbose  | Version 
282 >     | Input String | Output String | LibDir String
283 >       deriving Show
284 >    
285 >    options :: [OptDescr Flag]
286 >    options =
287 >     [ Option ['v']     ["verbose"] (NoArg Verbose)       "chatty output on stderr"
288 >     , Option ['V','?'] ["version"] (NoArg Version)       "show version number"
289 >     , Option ['o']     ["output"]  (OptArg outp "FILE")  "output FILE"
290 >     , Option ['c']     []          (OptArg inp  "FILE")  "input FILE"
291 >     , Option ['L']     ["libdir"]  (ReqArg LibDir "DIR") "library directory"
292 >     ]
293 >    
294 >    inp,outp :: Maybe String -> Flag
295 >    outp = Output . fromMaybe "stdout"
296 >    inp  = Input  . fromMaybe "stdin"
297 >    
298 >    compilerOpts :: [String] -> IO ([Flag], [String])
299 >    compilerOpts argv = 
300 >       case getOpt Permute options argv of
301 >          (o,n,[]  ) -> return (o,n)
302 >          (_,_,errs) -> ioError (userError (concat errs ++ usageInfo header options))
303 >      where header = "Usage: ic [OPTION...] files..."
304
305 -}