summaryrefslogtreecommitdiffstats
diff options
context:
space:
mode:
-rw-r--r--stdlib/arg.ml7
-rw-r--r--stdlib/arg.mli8
-rw-r--r--stdlib/random.ml10
3 files changed, 13 insertions, 12 deletions
diff --git a/stdlib/arg.ml b/stdlib/arg.ml
index c3e7593ba..1de0a785f 100644
--- a/stdlib/arg.ml
+++ b/stdlib/arg.ml
@@ -44,6 +44,8 @@ let usage speclist errmsg =
List.iter (function (key, _, doc) -> eprintf " %s %s\n" key doc) speclist;
try ignore (assoc3 "-help" speclist)
with Not_found -> eprintf " -help display this list of options\n";
+ try ignore (assoc3 "--help" speclist)
+ with Not_found -> eprintf " --help display this list of options\n";
;;
let current = ref 0;;
@@ -55,6 +57,7 @@ let parse speclist anonfun errmsg =
if initpos < Array.length Sys.argv then Sys.argv.(initpos) else "(?)" in
begin match error with
| Unknown "-help" -> ()
+ | Unknown "--help" -> ()
| Unknown s ->
eprintf "%s: unknown option `%s'.\n" progname s
| Missing s ->
@@ -66,7 +69,9 @@ let parse speclist anonfun errmsg =
eprintf "%s: %s.\n" progname s
end;
usage speclist errmsg;
- exit (if error = (Unknown "-help") then 0 else 2);
+ if error = Unknow "-help" || error = Unknown "--help"
+ then exit 0
+ else exit 2
in
let l = Array.length Sys.argv in
incr current;
diff --git a/stdlib/arg.mli b/stdlib/arg.mli
index 77911b0e7..e6687b596 100644
--- a/stdlib/arg.mli
+++ b/stdlib/arg.mli
@@ -73,10 +73,10 @@ val parse : keywords:(string * spec * string) list ->
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
- display [usage_msg] and the list of options, and exit the program.
- You can override this behaviour by specifying your own [-help]
- option 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].
*)
exception Bad of string
diff --git a/stdlib/random.ml b/stdlib/random.ml
index ca6ad5bb3..c9bdeea76 100644
--- a/stdlib/random.ml
+++ b/stdlib/random.ml
@@ -61,19 +61,15 @@ let int bound =
let float bound = rawfloat () *. bound
(* Simple initialisation. The seed is an integer.
- Two seeds that are close enough will not produce uncorrelated
- pseudo-random sequences.
*)
let init seed =
- let st = ref seed in
- let mdg () =
- st := !st + 1;
- let d = Digest.string (string_of_int !st) in
+ let mdg i =
+ let d = Digest.string (string_of_int i ^ string_of_int seed) in
(Char.code d.[0] + (Char.code d.[1] lsl 8) + (Char.code d.[2] lsl 16))
lxor (Char.code d.[3] lsl 22)
in
for i = 0 to 54 do
- state.(i) <- (mdg ())
+ state.(i) <- (mdg i)
done;
index := 0