]> rtime.felk.cvut.cz Git - l4.git/blob - l4/pkg/ocaml/contrib/stdlib/arg.mli
update
[l4.git] / l4 / pkg / ocaml / contrib / stdlib / arg.mli
1 (***********************************************************************)
2 (*                                                                     *)
3 (*                           Objective Caml                            *)
4 (*                                                                     *)
5 (*             Damien Doligez, projet Para, INRIA Rocquencourt         *)
6 (*                                                                     *)
7 (*  Copyright 1996 Institut National de Recherche en Informatique et   *)
8 (*  en Automatique.  All rights reserved.  This file is distributed    *)
9 (*  under the terms of the GNU Library General Public License, with    *)
10 (*  the special exception on linking described in file ../LICENSE.     *)
11 (*                                                                     *)
12 (***********************************************************************)
13
14 (* $Id: arg.mli 8768 2008-01-11 16:13:18Z doligez $ *)
15
16 (** Parsing of command line arguments.
17
18    This module provides a general mechanism for extracting options and
19    arguments from the command line to the program.
20
21    Syntax of command lines:
22     A keyword is a character string starting with a [-].
23     An option is a keyword alone or followed by an argument.
24     The types of keywords are: [Unit], [Bool], [Set], [Clear],
25     [String], [Set_string], [Int], [Set_int], [Float], [Set_float],
26     [Tuple], [Symbol], and [Rest].
27     [Unit], [Set] and [Clear] keywords take no argument. A [Rest]
28     keyword takes the remaining of the command line as arguments.
29     Every other keyword takes the following word on the command line
30     as argument.
31     Arguments not preceded by a keyword are called anonymous arguments.
32
33    Examples ([cmd] is assumed to be the command name):
34 -   [cmd -flag           ](a unit option)
35 -   [cmd -int 1          ](an int option with argument [1])
36 -   [cmd -string foobar  ](a string option with argument ["foobar"])
37 -   [cmd -float 12.34    ](a float option with argument [12.34])
38 -   [cmd a b c           ](three anonymous arguments: ["a"], ["b"], and ["c"])
39 -   [cmd a b -- c d      ](two anonymous arguments and a rest option with
40                            two arguments)
41 *)
42
43 type spec =
44   | Unit of (unit -> unit)     (** Call the function with unit argument *)
45   | Bool of (bool -> unit)     (** Call the function with a bool argument *)
46   | Set of bool ref            (** Set the reference to true *)
47   | Clear of bool ref          (** Set the reference to false *)
48   | String of (string -> unit) (** Call the function with a string argument *)
49   | Set_string of string ref   (** Set the reference to the string argument *)
50   | Int of (int -> unit)       (** Call the function with an int argument *)
51   | Set_int of int ref         (** Set the reference to the int argument *)
52   | Float of (float -> unit)   (** Call the function with a float argument *)
53   | Set_float of float ref     (** Set the reference to the float argument *)
54   | Tuple of spec list         (** Take several arguments according to the
55                                    spec list *)
56   | Symbol of string list * (string -> unit)
57                                (** Take one of the symbols as argument and
58                                    call the function with the symbol *)
59   | Rest of (string -> unit)   (** Stop interpreting keywords and call the
60                                    function with each remaining argument *)
61 (** The concrete type describing the behavior associated
62    with a keyword. *)
63
64 type key = string
65 type doc = string
66 type usage_msg = string
67 type anon_fun = (string -> unit)
68
69 val parse :
70   (key * spec * doc) list -> anon_fun -> usage_msg -> unit
71 (** [Arg.parse speclist anon_fun usage_msg] parses the command line.
72     [speclist] is a list of triples [(key, spec, doc)].
73     [key] is the option keyword, it must start with a ['-'] character.
74     [spec] gives the option type and the function to call when this option
75     is found on the command line.
76     [doc] is a one-line description of this option.
77     [anon_fun] is called on anonymous arguments.
78     The functions in [spec] and [anon_fun] are called in the same order
79     as their arguments appear on the command line.
80
81     If an error occurs, [Arg.parse] exits the program, after printing
82     an error message as follows:
83 -   The reason for the error: unknown option, invalid or missing argument, etc.
84 -   [usage_msg]
85 -   The list of options, each followed by the corresponding [doc] string.
86
87     For the user to be able to specify anonymous arguments starting with a
88     [-], include for example [("-", String anon_fun, doc)] in [speclist].
89
90     By default, [parse] recognizes two unit options, [-help] and [--help],
91     which will display [usage_msg] and the list of options, and exit
92     the program.  You can override this behaviour by specifying your
93     own [-help] and [--help] options in [speclist].
94 *)
95
96 val parse_argv : ?current: int ref -> string array ->
97   (key * spec * doc) list -> anon_fun -> usage_msg -> unit
98 (** [Arg.parse_argv ~current args speclist anon_fun usage_msg] parses
99   the array [args] as if it were the command line.  It uses and updates
100   the value of [~current] (if given), or [Arg.current].  You must set
101   it before calling [parse_argv].  The initial value of [current]
102   is the index of the program name (argument 0) in the array.
103   If an error occurs, [Arg.parse_argv] raises [Arg.Bad] with
104   the error message as argument.  If option [-help] or [--help] is
105   given, [Arg.parse_argv] raises [Arg.Help] with the help message
106   as argument.
107 *)
108
109 exception Help of string
110 (** Raised by [Arg.parse_argv] when the user asks for help. *)
111
112 exception Bad of string
113 (** Functions in [spec] or [anon_fun] can raise [Arg.Bad] with an error
114     message to reject invalid arguments.
115     [Arg.Bad] is also raised by [Arg.parse_argv] in case of an error. *)
116
117 val usage : (key * spec * doc) list -> usage_msg -> unit
118 (** [Arg.usage speclist usage_msg] prints an error message including
119     the list of valid options.  This is the same message that
120     {!Arg.parse} prints in case of error.
121     [speclist] and [usage_msg] are the same as for [Arg.parse]. *)
122
123 val align: (key * spec * doc) list -> (key * spec * doc) list;;
124 (** Align the documentation strings by inserting spaces at the first
125     space, according to the length of the keyword.  Use a
126     space as the first character in a doc string if you want to
127     align the whole string.  The doc strings corresponding to
128     [Symbol] arguments are aligned on the next line. *)
129
130 val current : int ref
131 (** Position (in {!Sys.argv}) of the argument being processed.  You can
132     change this value, e.g. to force {!Arg.parse} to skip some arguments.
133     {!Arg.parse} uses the initial value of {!Arg.current} as the index of
134     argument 0 (the program name) and starts parsing arguments
135     at the next element. *)