summaryrefslogtreecommitdiffstats
path: root/stdlib/arg.ml
diff options
context:
space:
mode:
authorDamien Doligez <damien.doligez-inria.fr>1998-04-06 16:33:34 +0000
committerDamien Doligez <damien.doligez-inria.fr>1998-04-06 16:33:34 +0000
commit1f39b97ded18281e45c0cd9ae196ace338409308 (patch)
tree14775b6e2b080345771265bb6253be78e906a281 /stdlib/arg.ml
parentd42d481cb75570d23fe6894546657f9884682178 (diff)
Ajout Arg.Rest.
git-svn-id: http://caml.inria.fr/svn/ocaml/trunk@1906 f963ae5c-01c2-4b8c-9fe0-0dff7051ff02
Diffstat (limited to 'stdlib/arg.ml')
-rw-r--r--stdlib/arg.ml7
1 files changed, 7 insertions, 0 deletions
diff --git a/stdlib/arg.ml b/stdlib/arg.ml
index 8bbb56ffd..d0c20e26b 100644
--- a/stdlib/arg.ml
+++ b/stdlib/arg.ml
@@ -18,6 +18,8 @@ type spec =
| 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 *)
+ | Rest of (string -> unit) (* Stop interpreting keywords and call the
+ function with each remaining argument *)
exception Bad of string
@@ -91,6 +93,11 @@ let parse speclist anonfun errmsg =
let arg = Sys.argv.(!current+1) in
f (float_of_string arg);
incr current;
+ | Rest f ->
+ while !current < l-1 do
+ f Sys.argv.(!current+1);
+ incr current;
+ done;
| _ -> stop (Missing s)
with Bad m -> stop (Message m);
end;