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
|
|
|
(* *)
|
1999-11-29 11:04:07 -08:00
|
|
|
(* Damien Doligez, projet Para, INRIA Rocquencourt *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
1996-04-30 07:53:58 -07:00
|
|
|
(* Copyright 1996 Institut National de Recherche en Informatique et *)
|
1999-11-17 10:59:06 -08:00
|
|
|
(* en Automatique. All rights reserved. This file is distributed *)
|
2001-12-07 05:41:02 -08:00
|
|
|
(* under the terms of the GNU Library General Public License, with *)
|
|
|
|
(* the special exception on linking described in file ../LICENSE. *)
|
1995-08-09 08:06:35 -07:00
|
|
|
(* *)
|
|
|
|
(***********************************************************************)
|
|
|
|
|
|
|
|
(* $Id$ *)
|
|
|
|
|
2002-12-08 07:17:30 -08:00
|
|
|
type key = string
|
|
|
|
type doc = string
|
|
|
|
type usage_msg = string
|
2003-03-12 08:36:28 -08:00
|
|
|
type anon_fun = (string -> unit)
|
2002-12-08 07:17:30 -08:00
|
|
|
|
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 *)
|
2003-04-25 03:19:35 -07:00
|
|
|
| Bool of (bool -> unit) (* Call the function with a bool 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 *)
|
2003-04-25 03:19:35 -07:00
|
|
|
| Set_string of string ref (* Set the reference to the string argument *)
|
1995-09-05 05:30:26 -07:00
|
|
|
| Int of (int -> unit) (* Call the function with an int argument *)
|
2003-04-25 03:19:35 -07:00
|
|
|
| Set_int of int ref (* Set the reference to the int argument *)
|
1995-09-05 05:30:26 -07:00
|
|
|
| Float of (float -> unit) (* Call the function with a float argument *)
|
2003-04-25 03:19:35 -07:00
|
|
|
| Set_float of float ref (* Set the reference to the float argument *)
|
|
|
|
| Tuple of spec list (* Take several arguments according to the
|
|
|
|
spec list *)
|
2002-11-02 13:24:30 -08:00
|
|
|
| Symbol of string list * (string -> unit)
|
2003-04-25 03:19:35 -07:00
|
|
|
(* Take one of the symbols as argument and
|
|
|
|
call the function with the symbol. *)
|
1998-04-06 09:33:34 -07:00
|
|
|
| Rest of (string -> unit) (* Stop interpreting keywords and call the
|
|
|
|
function with each remaining argument *)
|
1995-05-04 03:15:53 -07:00
|
|
|
|
|
|
|
exception Bad of string
|
|
|
|
|
|
|
|
type error =
|
1996-10-24 07:17:48 -07:00
|
|
|
| Unknown of string
|
1995-05-04 03:15:53 -07:00
|
|
|
| Wrong of string * string * string (* option, actual, expected *)
|
|
|
|
| Missing of string
|
|
|
|
| Message of string
|
|
|
|
|
|
|
|
open Printf
|
|
|
|
|
1996-10-24 07:17:48 -07:00
|
|
|
let rec assoc3 x l =
|
|
|
|
match l with
|
|
|
|
| [] -> raise Not_found
|
2002-12-08 07:17:30 -08:00
|
|
|
| (y1, y2, y3) :: t when y1 = x -> y2
|
|
|
|
| _ :: t -> assoc3 x t
|
1996-10-24 07:17:48 -07:00
|
|
|
;;
|
1995-05-04 03:15:53 -07:00
|
|
|
|
2002-11-02 13:47:02 -08:00
|
|
|
let make_symlist prefix sep suffix l =
|
2002-11-02 13:24:30 -08:00
|
|
|
match l with
|
|
|
|
| [] -> "<none>"
|
2002-11-02 13:47:02 -08:00
|
|
|
| h::t -> (List.fold_left (fun x y -> x ^ sep ^ y) (prefix ^ h) t) ^ suffix
|
2002-11-02 13:24:30 -08:00
|
|
|
;;
|
|
|
|
|
|
|
|
let print_spec (key, spec, doc) =
|
|
|
|
match spec with
|
|
|
|
| Symbol (l, _) -> eprintf " %s %s %s\n" key (make_symlist "{" "|" "}" l) doc
|
|
|
|
| _ -> eprintf " %s %s\n" key doc
|
|
|
|
;;
|
|
|
|
|
1996-10-24 08:19:22 -07:00
|
|
|
let usage speclist errmsg =
|
|
|
|
eprintf "%s\n" errmsg;
|
2002-11-02 13:24:30 -08:00
|
|
|
List.iter print_spec speclist;
|
2001-02-05 06:59:24 -08:00
|
|
|
try ignore (assoc3 "-help" speclist)
|
2002-11-02 13:24:30 -08:00
|
|
|
with Not_found -> eprintf " -help Display this list of options\n";
|
2001-08-21 08:10:51 -07:00
|
|
|
try ignore (assoc3 "--help" speclist)
|
2002-11-02 13:24:30 -08:00
|
|
|
with Not_found -> eprintf " --help Display this list of options\n";
|
1996-10-24 07:17:48 -07:00
|
|
|
;;
|
|
|
|
|
1997-07-03 07:15:35 -07:00
|
|
|
let current = ref 0;;
|
|
|
|
|
2003-06-12 04:13:40 -07:00
|
|
|
let parse_argv argv speclist anonfun errmsg =
|
1996-10-24 07:17:48 -07:00
|
|
|
let stop error =
|
2003-05-23 07:34:23 -07:00
|
|
|
let progname = if Array.length argv > 0 then argv.(0) else "(?)" in
|
1996-10-24 07:17:48 -07:00
|
|
|
begin match error with
|
1999-11-29 11:04:07 -08:00
|
|
|
| Unknown "-help" -> ()
|
2001-08-21 08:10:51 -07:00
|
|
|
| Unknown "--help" -> ()
|
1996-10-24 07:17:48 -07:00
|
|
|
| Unknown s ->
|
|
|
|
eprintf "%s: unknown option `%s'.\n" progname s
|
|
|
|
| Missing s ->
|
|
|
|
eprintf "%s: option `%s' needs an argument.\n" progname s
|
|
|
|
| Wrong (opt, arg, expected) ->
|
|
|
|
eprintf "%s: wrong argument `%s'; option `%s' expects %s.\n"
|
|
|
|
progname arg opt expected
|
|
|
|
| Message s ->
|
|
|
|
eprintf "%s: %s.\n" progname s
|
|
|
|
end;
|
1996-10-24 08:19:22 -07:00
|
|
|
usage speclist errmsg;
|
2001-08-21 11:49:22 -07:00
|
|
|
if error = Unknown "-help" || error = Unknown "--help"
|
2001-08-21 08:10:51 -07:00
|
|
|
then exit 0
|
|
|
|
else exit 2
|
1995-05-04 03:15:53 -07:00
|
|
|
in
|
2002-03-22 12:46:06 -08:00
|
|
|
let l = Array.length argv in
|
1997-07-03 07:15:35 -07:00
|
|
|
incr current;
|
|
|
|
while !current < l do
|
2002-03-22 12:46:06 -08:00
|
|
|
let s = argv.(!current) in
|
2000-12-28 05:07:42 -08:00
|
|
|
if String.length s >= 1 && String.get s 0 = '-' then begin
|
1997-07-03 07:15:35 -07:00
|
|
|
let action =
|
|
|
|
try assoc3 s speclist
|
|
|
|
with Not_found -> stop (Unknown s)
|
|
|
|
in
|
|
|
|
begin try
|
2003-04-25 03:19:35 -07:00
|
|
|
let rec treat_action = function
|
1997-07-03 07:15:35 -07:00
|
|
|
| Unit f -> f ();
|
2003-04-25 03:19:35 -07:00
|
|
|
| Bool f ->
|
|
|
|
let arg = argv.(!current + 1) in
|
|
|
|
begin try f (bool_of_string arg)
|
|
|
|
with Invalid_argument "bool_of_string" ->
|
|
|
|
stop (Wrong (s, arg, "a boolean"))
|
|
|
|
end;
|
|
|
|
incr current;
|
1997-07-03 07:15:35 -07:00
|
|
|
| Set r -> r := true;
|
|
|
|
| Clear r -> r := false;
|
|
|
|
| String f when !current + 1 < l ->
|
2002-12-08 07:17:30 -08:00
|
|
|
f argv.(!current + 1);
|
2002-11-02 13:24:30 -08:00
|
|
|
incr current;
|
|
|
|
| Symbol (symb, f) when !current + 1 < l ->
|
2002-12-08 07:17:30 -08:00
|
|
|
let arg = argv.(!current + 1) in
|
2002-11-02 13:24:30 -08:00
|
|
|
if List.mem arg symb then begin
|
2002-12-08 07:17:30 -08:00
|
|
|
f argv.(!current + 1);
|
2002-11-02 13:24:30 -08:00
|
|
|
incr current;
|
|
|
|
end else begin
|
2002-11-02 13:47:02 -08:00
|
|
|
stop (Wrong (s, arg, "one of: " ^ (make_symlist "" " " "" symb)))
|
2002-11-02 13:24:30 -08:00
|
|
|
end
|
|
|
|
| Set_string r when !current + 1 < l ->
|
2002-12-08 07:17:30 -08:00
|
|
|
r := argv.(!current + 1);
|
1997-07-03 07:15:35 -07:00
|
|
|
incr current;
|
|
|
|
| Int f when !current + 1 < l ->
|
2002-12-08 07:17:30 -08:00
|
|
|
let arg = argv.(!current + 1) in
|
1997-07-03 07:15:35 -07:00
|
|
|
begin try f (int_of_string arg)
|
|
|
|
with Failure "int_of_string" -> stop (Wrong (s, arg, "an integer"))
|
|
|
|
end;
|
|
|
|
incr current;
|
2002-11-02 13:24:30 -08:00
|
|
|
| Set_int r when !current + 1 < l ->
|
2002-12-08 07:17:30 -08:00
|
|
|
let arg = argv.(!current + 1) in
|
2002-11-02 13:24:30 -08:00
|
|
|
begin try r := (int_of_string arg)
|
|
|
|
with Failure "int_of_string" -> stop (Wrong (s, arg, "an integer"))
|
|
|
|
end;
|
|
|
|
incr current;
|
1997-07-03 07:15:35 -07:00
|
|
|
| Float f when !current + 1 < l ->
|
2002-12-08 07:17:30 -08:00
|
|
|
let arg = argv.(!current + 1) in
|
2002-03-21 02:45:20 -08:00
|
|
|
begin try f (float_of_string arg);
|
|
|
|
with Failure "float_of_string" -> stop (Wrong (s, arg, "a float"))
|
|
|
|
end;
|
1997-07-03 07:15:35 -07:00
|
|
|
incr current;
|
2002-11-02 13:24:30 -08:00
|
|
|
| Set_float r when !current + 1 < l ->
|
2002-12-08 07:17:30 -08:00
|
|
|
let arg = argv.(!current + 1) in
|
2002-11-02 13:24:30 -08:00
|
|
|
begin try r := (float_of_string arg);
|
|
|
|
with Failure "float_of_string" -> stop (Wrong (s, arg, "a float"))
|
|
|
|
end;
|
|
|
|
incr current;
|
2003-04-25 03:19:35 -07:00
|
|
|
| Tuple specs ->
|
|
|
|
List.iter treat_action specs;
|
1998-04-06 09:33:34 -07:00
|
|
|
| Rest f ->
|
2002-12-08 07:17:30 -08:00
|
|
|
while !current < l - 1 do
|
|
|
|
f argv.(!current + 1);
|
1998-04-06 09:33:34 -07:00
|
|
|
incr current;
|
|
|
|
done;
|
2003-04-25 03:19:35 -07:00
|
|
|
| _ -> stop (Missing s) in
|
|
|
|
treat_action action
|
1997-07-03 07:15:35 -07:00
|
|
|
with Bad m -> stop (Message m);
|
|
|
|
end;
|
|
|
|
incr current;
|
|
|
|
end else begin
|
|
|
|
(try anonfun s with Bad m -> stop (Message m));
|
|
|
|
incr current;
|
|
|
|
end;
|
|
|
|
done;
|
|
|
|
;;
|
2002-03-22 12:46:06 -08:00
|
|
|
|
2003-06-12 04:13:40 -07:00
|
|
|
let parse =
|
2003-05-23 07:34:23 -07:00
|
|
|
current := 0;
|
2003-06-12 04:13:40 -07:00
|
|
|
parse_argv Sys.argv;
|
2003-05-23 07:34:23 -07:00
|
|
|
;;
|