summaryrefslogtreecommitdiffstats
path: root/stdlib/arg.mli
blob: fa54cebc457d40aa35d5264e634497385627462c (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
(***********************************************************************)
(*                                                                     *)
(*                           Objective Caml                            *)
(*                                                                     *)
(*             Damien Doligez, projet Para, INRIA Rocquencourt         *)
(*                                                                     *)
(*  Copyright 1996 Institut National de Recherche en Informatique et   *)
(*  en Automatique.  All rights reserved.  This file is distributed    *)
(*  under the terms of the GNU Library General Public License, with    *)
(*  the special exception on linking described in file ../LICENSE.     *)
(*                                                                     *)
(***********************************************************************)

(* $Id$ *)

(** Parsing of command line arguments.

   This module provides a general mechanism for extracting options and
   arguments from the command line to the program.

   Syntax of command lines:
    A keyword is a character string starting with a [-].
    An option is a keyword alone or followed by an argument.
    The types of keywords are: [Unit], [Bool], [Set], [Clear],
    [String], [Set_string], [Int], [Set_int], [Float], [Set_float],
    [Tuple], [Symbol], and [Rest].
    [Unit], [Set] and [Clear] keywords take no argument. A [Rest]
    keyword takes the remaining of the command line as arguments.
    Every other keyword takes the following word on the command line
    as argument.
    Arguments not preceded by a keyword are called anonymous arguments.

   Examples ([cmd] is assumed to be the command name):
-   [cmd -flag           ](a unit option)
-   [cmd -int 1          ](an int option with argument [1])
-   [cmd -string foobar  ](a string option with argument ["foobar"])
-   [cmd -float 12.34    ](a float option with argument [12.34])
-   [cmd a b c           ](three anonymous arguments: ["a"], ["b"], and ["c"])
-   [cmd a b -- c d      ](two anonymous arguments and a rest option with
                           two arguments)
*)

type spec =
  | Unit of (unit -> unit)     (** Call the function with unit argument *)
  | Bool of (bool -> unit)     (** Call the function with a bool argument *)
  | Set of bool ref            (** Set the reference to true *)
  | Clear of bool ref          (** Set the reference to false *)
  | String of (string -> unit) (** Call the function with a string argument *)
  | Set_string of string ref   (** Set the reference to the string argument *)
  | Int of (int -> unit)       (** Call the function with an int argument *)
  | Set_int of int ref         (** Set the reference to the int argument *)
  | Float of (float -> unit)   (** Call the function with a float argument *)
  | Set_float of float ref     (** Set the reference to the float argument *)
  | Tuple of spec list         (** Take several arguments according to the
                                   spec list *)
  | Symbol of string list * (string -> unit)
                               (** Take one of the symbols as argument and
                                   call the function with the symbol *)
  | Rest of (string -> unit)   (** Stop interpreting keywords and call the 
                                   function with each remaining argument *)

(** The concrete type describing the behavior associated
   with a keyword. *)

type key = string
type doc = string
type usage_msg = string
type anon_fun = (string -> unit)

val parse :
  (key * spec * doc) list -> anon_fun -> usage_msg -> unit
(** [Arg.parse speclist anon_fun usage_msg] parses the command line.
    [speclist] is a list of triples [(key, spec, doc)].
    [key] is the option keyword, it must start with a ['-'] character.
    [spec] gives the option type and the function to call when this option
    is found on the command line.
    [doc] is a one-line description of this option.
    [anon_fun] is called on anonymous arguments.
    The functions in [spec] and [anon_fun] are called in the same order
    as their arguments appear on the command line.

    If an error occurs, [Arg.parse] exits the program, after printing
    an error message as follows:
-   The reason for the error: unknown option, invalid or missing argument, etc.
-   [usage_msg]
-   The list of options, each followed by the corresponding [doc] string.

    For the user to be able to specify anonymous arguments starting with a
    [-], include for example [("-", String anon_fun, doc)] in [speclist].

    By default, [parse] recognizes two unit options, [-help] and [--help],
    which will display [usage_msg] and the list of options, and exit
    the program.  You can override this behaviour by specifying your
    own [-help] and [--help] options in [speclist].
*)

val parse_argv : string array ->
  (key * spec * doc) list -> anon_fun -> usage_msg -> unit
(** [Arg.parse_argv args speclist anon_fun usage_msg] parses the array
  [args] as if it were the command line.  It uses and updates the
  value of [Arg.current].  You must set [Arg.current] before calling
  [parse_argv], and restore it afterward if needed.
  If an error occurs, [Arg.parse_argv] raises [Arg.Bad] with
  the error message as argument.  If option [-help] or [--help] is
  given, [Arg.parse_argv] raises [Arg.Help] with the help message
  as argument.
*)

exception Help of string
(** Raised by [Arg.parse_argv] when the user asks for help. *)

exception Bad of string
(** Functions in [spec] or [anon_fun] can raise [Arg.Bad] with an error
    message to reject invalid arguments.
    [Arg.Bad] is also raised by [Arg.parse_argv] in case of an error. *)

val usage : (key * spec * doc) list -> usage_msg -> unit
(** [Arg.usage speclist usage_msg] prints an error message including
    the list of valid options.  This is the same message that
    {!Arg.parse} prints in case of error.
    [speclist] and [usage_msg] are the same as for [Arg.parse]. *)

val current : int ref
(** Position (in {!Sys.argv}) of the argument being processed.  You can
    change this value, e.g. to force {!Arg.parse} to skip some arguments.*)