summaryrefslogtreecommitdiffstats
path: root/stdlib
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib')
-rwxr-xr-xstdlib/Makefile.shared2
-rw-r--r--stdlib/camlinternalOO.ml3
-rw-r--r--stdlib/filename.ml2
-rw-r--r--stdlib/parsing.ml3
-rw-r--r--stdlib/printexc.ml2
-rw-r--r--stdlib/weak.ml2
6 files changed, 11 insertions, 3 deletions
diff --git a/stdlib/Makefile.shared b/stdlib/Makefile.shared
index daf266268..b94c481d4 100755
--- a/stdlib/Makefile.shared
+++ b/stdlib/Makefile.shared
@@ -17,7 +17,7 @@ include ../config/Makefile
RUNTIME=../boot/ocamlrun
COMPILER=../ocamlc
CAMLC=$(RUNTIME) $(COMPILER)
-COMPFLAGS=-strict-sequence -w +33 -g -warn-error A -nostdlib
+COMPFLAGS=-strict-sequence -w +33..38 -g -warn-error A -nostdlib
OPTCOMPILER=../ocamlopt
CAMLOPT=$(RUNTIME) $(OPTCOMPILER)
OPTCOMPFLAGS=-warn-error A -nostdlib -g
diff --git a/stdlib/camlinternalOO.ml b/stdlib/camlinternalOO.ml
index 6d7871465..1abb7e550 100644
--- a/stdlib/camlinternalOO.ml
+++ b/stdlib/camlinternalOO.ml
@@ -58,6 +58,7 @@ let initial_object_size = 2
(**** Items ****)
type item = DummyA | DummyB | DummyC of int
+let _ = [DummyA; DummyB; DummyC 0] (* to avoid warnings *)
let dummy_item = (magic () : item)
@@ -67,6 +68,8 @@ type tag
type label = int
type closure = item
type t = DummyA | DummyB | DummyC of int
+let _ = [DummyA; DummyB; DummyC 0] (* to avoid warnings *)
+
type obj = t array
external ret : (obj -> 'a) -> closure = "%identity"
diff --git a/stdlib/filename.ml b/stdlib/filename.ml
index 950a7b39f..89a349df3 100644
--- a/stdlib/filename.ml
+++ b/stdlib/filename.ml
@@ -132,7 +132,7 @@ module Win32 = struct
| '\\' -> loop_bs (n+1) (i+1);
| c -> add_bs n; loop i
end
- and add_bs n = for j = 1 to n do Buffer.add_char b '\\'; done
+ and add_bs n = for _j = 1 to n do Buffer.add_char b '\\'; done
in
loop 0;
Buffer.contents b
diff --git a/stdlib/parsing.ml b/stdlib/parsing.ml
index 55a8f53aa..a10ffe2c1 100644
--- a/stdlib/parsing.ml
+++ b/stdlib/parsing.ml
@@ -74,6 +74,9 @@ type parser_output =
| Compute_semantic_action
| Call_error_function
+(* to avoid warnings *)
+let _ = [Read_token; Raise_parse_error; Grow_stacks_1; Grow_stacks_2; Compute_semantic_action; Call_error_function]
+
external parse_engine :
parse_tables -> parser_env -> parser_input -> Obj.t -> parser_output
= "caml_parse_engine"
diff --git a/stdlib/printexc.ml b/stdlib/printexc.ml
index 062decb85..f244009ba 100644
--- a/stdlib/printexc.ml
+++ b/stdlib/printexc.ml
@@ -88,6 +88,8 @@ type loc_info =
* int (* end char *)
| Unknown_location of bool (*is_raise*)
+let _ = [Known_location (false, "", 0, 0, 0); Unknown_location false]
+
external get_exception_backtrace:
unit -> loc_info array option = "caml_get_exception_backtrace"
diff --git a/stdlib/weak.ml b/stdlib/weak.ml
index bbd3debc4..ab0bab0f6 100644
--- a/stdlib/weak.ml
+++ b/stdlib/weak.ml
@@ -209,7 +209,7 @@ module Make (H : Hashtbl.HashedType) : (S with type data = H.t) = struct
t.hashes.(index) <- newhashes;
if sz <= t.limit && newsz > t.limit then begin
t.oversize <- t.oversize + 1;
- for i = 0 to over_limit do test_shrink_bucket t done;
+ for _i = 0 to over_limit do test_shrink_bucket t done;
end;
if t.oversize > Array.length t.table / over_limit then resize t;
end else if check bucket i then begin