1995-08-09 08:06:35 -07:00
|
|
|
(***********************************************************************)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Objective Caml *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(* Xavier Leroy, projet Cristal, INRIA Rocquencourt *)
|
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* Automatique. Distributed only by permission. *)
|
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
1995-08-09 06:15:01 -07:00
|
|
|
(* Module [Arg]: parsing of command line arguments *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* This module provides a general mechanism for extracting options and
|
1996-10-24 07:17:48 -07:00
|
|
|
arguments from the command line to the program.
|
|
|
|
*)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* Syntax of command lines:
|
|
|
|
A keyword is a character string starting with a [-].
|
|
|
|
An option is a keyword alone or followed by an argument.
|
1996-10-24 07:17:48 -07:00
|
|
|
There are six types of keywords: [Unit], [Set], [Clear], [String],
|
|
|
|
[Int], and [Float]. [Unit], [Set] and [Clear] keywords take no
|
|
|
|
argument. [String], [Int], and [Float] keywords take the following
|
|
|
|
word on the command line as an argument.
|
|
|
|
Arguments not preceded by a keyword are called anonymous arguments.
|
|
|
|
*)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
(* 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])
|
1996-10-24 07:17:48 -07:00
|
|
|
- [cmd a b c ](three anonymous arguments: ["a"], ["b"], and ["c"])
|
1995-05-04 03:15:53 -07:00
|
|
|
*)
|
|
|
|
|
|
|
|
type spec =
|
1997-09-11 08:10:23 -07:00
|
|
|
| Unit of (unit -> unit) (* Call the function with unit argument *)
|
1995-09-05 05:30:26 -07:00
|
|
|
| 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 *)
|
|
|
|
| Int of (int -> unit) (* Call the function with an int argument *)
|
|
|
|
| Float of (float -> unit) (* Call the function with a float argument *)
|
1995-05-04 03:15:53 -07:00
|
|
|
(* The concrete type describing the behavior associated
|
|
|
|
with a keyword. *)
|
|
|
|
|
1996-10-24 07:17:48 -07:00
|
|
|
val parse : (string * spec * string) list -> (string -> unit) -> string -> unit
|
|
|
|
(*
|
1997-05-21 08:28:30 -07:00
|
|
|
[parse speclist anonfun usage_msg] parses the command line.
|
1996-10-24 07:17:48 -07:00
|
|
|
[speclist] is a list of triples [(key, spec, doc)].
|
1997-07-03 07:15:35 -07:00
|
|
|
[key] is the option keyword, it must start with a ['-'] character.
|
1996-10-24 07:17:48 -07:00
|
|
|
[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.
|
|
|
|
[anonfun] is called on anonymous arguments.
|
|
|
|
The functions in [spec] and [anonfun] are called in the same order
|
|
|
|
as their arguments appear on the command line.
|
|
|
|
|
|
|
|
If an error occurs, [parse] exits the program, after printing an error
|
|
|
|
message as follows:
|
|
|
|
- The reason for the error: unknown option, invalid or missing argument, etc.
|
1997-05-21 08:28:30 -07:00
|
|
|
- [usage_msg]
|
1996-10-24 07:17:48 -07:00
|
|
|
- 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 anonfun, doc)] in [speclist].
|
|
|
|
|
|
|
|
By default, [parse] recognizes a unit option [-help], which will
|
1997-05-21 08:28:30 -07:00
|
|
|
display [usage_msg] and the list of options, and exit the program.
|
1996-10-24 07:17:48 -07:00
|
|
|
You can override this behaviour by specifying your own [-help]
|
|
|
|
option in [speclist].
|
|
|
|
*)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
exception Bad of string
|
1997-11-05 11:44:08 -08:00
|
|
|
(*
|
|
|
|
Functions in [spec] or [anonfun] can raise [Bad] with an error
|
|
|
|
message to reject invalid arguments.
|
|
|
|
*)
|
1996-10-24 08:19:22 -07:00
|
|
|
|
|
|
|
val usage: (string * spec * string) list -> string -> unit
|
|
|
|
(*
|
1997-05-21 08:28:30 -07:00
|
|
|
[usage speclist usage_msg]
|
|
|
|
[speclist] and [usage_msg] are the same as for [parse]. [usage]
|
1997-07-03 07:15:35 -07:00
|
|
|
prints the same error message that [parse] prints in case of error.
|
|
|
|
*)
|
|
|
|
|
|
|
|
val current: int ref;;
|
|
|
|
(*
|
1997-11-05 11:44:08 -08:00
|
|
|
Position (in [Sys.argv]) of the argument being processed. You can
|
|
|
|
change this value, e.g. to force [parse] to skip some arguments.
|
1996-10-24 08:19:22 -07:00
|
|
|
*)
|