Merge pull request #9657 from nojb/warning_mnemonics

Add mnemonics for warnings
master
Gabriel Scherer 2020-07-21 11:47:37 +02:00 committed by GitHub
commit b1d1c0b77c
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
112 changed files with 864 additions and 652 deletions

View File

@ -220,6 +220,12 @@ Working version
(Xavier Van de Woestyne, report by whitequark, review by Florian Angeletti
and Gabriel Scherer)
- #9657: Warnings can now be referred to by their mnemonic name. The names are
displayed using `-warn-help` and can be utilized anywhere where a warning list
specification is expected, e.g. `[@@@ocaml.warning ...]`.
(Nicolás Ojeda Bär, review by Gabriel Scherer, Florian Angeletti and Leo
White)
### Internal/compiler-libs changes:
- #9216: add Lambda.duplicate which refreshes bound identifiers

View File

@ -188,7 +188,7 @@ let check_consistency file_name cu =
begin try
let source = List.assoc cu.cu_name !implementations_defined in
Location.prerr_warning (Location.in_file file_name)
(Warnings.Multiple_definition(cu.cu_name,
(Warnings.Module_linked_twice(cu.cu_name,
Location.show_filename file_name,
Location.show_filename source))
with Not_found -> ()

View File

@ -175,7 +175,7 @@ let file_aux ~tool_name inputfile (type a) parse_fun invariant_fun
Location.input_name := (input_value ic : string);
if !Clflags.unsafe then
Location.prerr_warning (Location.in_file !Location.input_name)
Warnings.Unsafe_without_parsing;
Warnings.Unsafe_array_syntax_without_parsing;
let ast = (input_value ic : a) in
if !Clflags.all_ppx = [] then invariant_fun ast;
(* if all_ppx <> [], invariant_fun will be called by apply_rewriters *)

View File

@ -619,9 +619,9 @@ let rec emit_tail_infos is_tail lambda =
But then this means getting different warnings depending
on whether the native or bytecode compiler is used. *)
if not is_tail
&& Warnings.is_active Warnings.Expect_tailcall
&& Warnings.is_active Warnings.Tailcall_expected
then Location.prerr_warning (to_location ap.ap_loc)
Warnings.Expect_tailcall;
Warnings.Tailcall_expected;
end;
emit_tail_infos false ap.ap_func;
list_emit_tail_infos false ap.ap_args
@ -887,6 +887,6 @@ let simplify_lambda lam =
|> simplify_exits
|> simplify_lets
in
if !Clflags.annotations || Warnings.is_active Warnings.Expect_tailcall
if !Clflags.annotations || Warnings.is_active Warnings.Tailcall_expected
then emit_tail_infos true lam;
lam

View File

@ -147,12 +147,13 @@ warnings-help.etex: $(SRC)/utils/warnings.ml $(SRC)/ocamlc
echo "% when a new warning is documented.";\
echo "%";\
$(SET_LD_PATH) $(SRC)/boot/ocamlrun $(SRC)/ocamlc -warn-help \
| sed -e 's/^ *\([0-9A-Z][0-9]*\)\(.*\)/\\item[\1] \2/'\
| sed -e 's/^ *\([0-9][0-9]*\) *\[\([a-z][a-z-]*\)\]\(.*\)/\\item[\1 "\2"] \3/' \
-e 's/^ *\([0-9A-Z][0-9]*\) *\([^]].*\)/\\item[\1] \2/'\
) >$@
# sed --inplace is not portable, emulate
for i in 52 57; do\
sed\
s'/\\item\['$$i'\]/\\item\['$$i' (see \\ref{ss:warn'$$i'})\]/'\
s'/\\item\[\('$$i'[^]]*\)\]/\\item\[\1 (see \\ref{ss:warn'$$i'})\]/'\
$@ > $@.tmp;\
mv $@.tmp $@;\
done

View File

@ -753,8 +753,18 @@ to \var{uppercase-letter}.
to \var{lowercase-letter}.
\end{options}
Warning numbers and letters which are out of the range of warnings
that are currently defined are ignored. The warnings are as follows.
Alternatively, \var{warning-list} can specify a single warning using its
mnemonic name (see below), as follows:
\begin{options}
\item["+"\var{name}] Enable warning \var{name}.
\item["-"\var{name}] Disable warning \var{name}.
\item["@"\var{name}] Enable and mark as fatal warning \var{name}.
\end{options}
Warning numbers, letters and names which are not currently defined are
ignored. The warnings are as follows (the name following each number specifies
the mnemonic for that warning).
\begin{options}
\input{warnings-help.tex}
\end{options}

View File

@ -1026,7 +1026,7 @@ and simplify_named env r (tree : Flambda.named) : Flambda.named * R.t =
[block_approx; _field_approx; value_approx] ->
if A.warn_on_mutation block_approx then begin
Location.prerr_warning (Debuginfo.to_location dbg)
Warnings.Assignment_to_non_mutable_value
Warnings.Flambda_assignment_to_non_mutable_value
end;
let kind =
let check () =
@ -1055,7 +1055,7 @@ and simplify_named env r (tree : Flambda.named) : Flambda.named * R.t =
| Psetfield _, _block::_, block_approx::_ ->
if A.warn_on_mutation block_approx then begin
Location.prerr_warning (Debuginfo.to_location dbg)
Warnings.Assignment_to_non_mutable_value
Warnings.Flambda_assignment_to_non_mutable_value
end;
tree, ret r (A.value_unknown Other)
| (Psetfield _ | Parraysetu _ | Parraysets _), _, _ ->

View File

@ -44,18 +44,18 @@ let docstrings : docstring list ref = ref []
(* Warn for unused and ambiguous docstrings *)
let warn_bad_docstrings () =
if Warnings.is_active (Warnings.Bad_docstring true) then begin
if Warnings.is_active (Warnings.Unexpected_docstring true) then begin
List.iter
(fun ds ->
match ds.ds_attached with
| Info -> ()
| Unattached ->
prerr_warning ds.ds_loc (Warnings.Bad_docstring true)
prerr_warning ds.ds_loc (Warnings.Unexpected_docstring true)
| Docs ->
match ds.ds_associated with
| Zero | One -> ()
| Many ->
prerr_warning ds.ds_loc (Warnings.Bad_docstring false))
prerr_warning ds.ds_loc (Warnings.Unexpected_docstring false))
(List.rev !docstrings)
end

View File

@ -1,2 +1,2 @@
File "0001-test.ml", line 1:
Warning 24: bad source file name: "0001-test" is not a valid module name.
Warning 24 [bad-module-name]: bad source file name: "0001-test" is not a valid module name.

View File

@ -1,60 +1,60 @@
File "morematch.ml", line 67, characters 2-5:
67 | | 4|5|7 -> 100
^^^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
File "morematch.ml", line 68, characters 2-3:
68 | | 7 | 8 -> 6
^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
File "morematch.ml", line 219, characters 33-47:
219 | let f = function (([]|[_]) as x)|(_::([] as x))|(_::_::x) -> x
^^^^^^^^^^^^^^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
File "morematch.ml", line 388, characters 2-15:
388 | | A,_,(100|103) -> 5
^^^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
File "morematch.ml", line 401, characters 2-20:
401 | | [],_,(100|103|104) -> 5
^^^^^^^^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
File "morematch.ml", line 402, characters 2-16:
402 | | [],_,(100|103) -> 6
^^^^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
File "morematch.ml", line 403, characters 2-29:
403 | | [],_,(1000|1001|1002|20000) -> 7
^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
File "morematch.ml", line 413, characters 5-12:
413 | | (100|103|101) -> 2
^^^^^^^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
File "morematch.ml", line 432, characters 43-44:
432 | | (J,J,((C|D) as x |E x|F (_,x))) | (J,_,((C|J) as x)) -> autre (x,x,x)
^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
File "morematch.ml", line 455, characters 7-8:
455 | | _,_,(X|U _) -> 8
^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
File "morematch.ml", line 456, characters 2-7:
456 | | _,_,Y -> 5
^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
File "morematch.ml", lines 1050-1053, characters 8-10:
1050 | ........function
1051 | | A (`A|`C) -> 0
1052 | | B (`B,`D) -> 1
1053 | | C -> 2
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
A `D
File "morematch.ml", line 1084, characters 5-51:
1084 | | _, _, _, _, _, A, _, _, _, _, B, _, _, _, _, _ -> "11"
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
File "morematch.ml", line 1086, characters 5-51:
1086 | | _, _, _, _, _, _, _, _, _, _, _, _, _, _, _, _ -> "13"
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.

View File

@ -4,7 +4,7 @@ File "robustmatch.ml", lines 33-37, characters 6-23:
35 | | MAB, _, A -> ()
36 | | _, AB, B -> ()
37 | | _, MAB, B -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(AB, MAB, A)
File "robustmatch.ml", lines 43-47, characters 4-21:
@ -13,42 +13,42 @@ File "robustmatch.ml", lines 43-47, characters 4-21:
45 | | MAB, _, A -> ()
46 | | _, AB, B -> ()
47 | | _, MAB, B -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(AB, MAB, A)
File "robustmatch.ml", lines 54-56, characters 4-27:
54 | ....match r1, r2, a with
55 | | R1, _, 0 -> ()
56 | | _, R2, "coucou" -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, 1)
File "robustmatch.ml", lines 64-66, characters 4-27:
64 | ....match r1, r2, a with
65 | | R1, _, A -> ()
66 | | _, R2, "coucou" -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, (B|C))
File "robustmatch.ml", lines 69-71, characters 4-20:
69 | ....match r1, r2, a with
70 | | _, R2, "coucou" -> ()
71 | | R1, _, A -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, (B|C))
File "robustmatch.ml", lines 74-76, characters 4-20:
74 | ....match r1, r2, a with
75 | | _, R2, "coucou" -> ()
76 | | R1, _, _ -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R2, R2, "")
File "robustmatch.ml", lines 85-87, characters 4-20:
85 | ....match r1, r2, a with
86 | | R1, _, A -> ()
87 | | _, R2, X -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, (B|C))
File "robustmatch.ml", lines 90-93, characters 4-20:
@ -56,35 +56,35 @@ File "robustmatch.ml", lines 90-93, characters 4-20:
91 | | R1, _, A -> ()
92 | | _, R2, X -> ()
93 | | R1, _, _ -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R2, R2, (Y|Z))
File "robustmatch.ml", lines 96-98, characters 4-20:
96 | ....match r1, r2, a with
97 | | R1, _, _ -> ()
98 | | _, R2, X -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R2, R2, (Y|Z))
File "robustmatch.ml", lines 107-109, characters 4-20:
107 | ....match r1, r2, a with
108 | | R1, _, A -> ()
109 | | _, R2, X -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, (B|C))
File "robustmatch.ml", lines 129-131, characters 4-20:
129 | ....match r1, r2, a with
130 | | R1, _, A -> ()
131 | | _, R2, X -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, B)
File "robustmatch.ml", lines 151-153, characters 4-20:
151 | ....match r1, r2, a with
152 | | R1, _, A -> ()
153 | | _, R2, X -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, B)
File "robustmatch.ml", lines 156-159, characters 4-20:
@ -92,21 +92,21 @@ File "robustmatch.ml", lines 156-159, characters 4-20:
157 | | R1, _, A -> ()
158 | | _, R2, X -> ()
159 | | R1, _, _ -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R2, R2, Y)
File "robustmatch.ml", lines 162-164, characters 4-20:
162 | ....match r1, r2, a with
163 | | R1, _, _ -> ()
164 | | _, R2, X -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R2, R2, Y)
File "robustmatch.ml", lines 167-169, characters 4-20:
167 | ....match r1, r2, a with
168 | | R1, _, C -> ()
169 | | _, R2, Y -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, A)
File "robustmatch.ml", lines 176-179, characters 4-20:
@ -114,14 +114,14 @@ File "robustmatch.ml", lines 176-179, characters 4-20:
177 | | _, R1, 0 -> ()
178 | | R2, _, [||] -> ()
179 | | _, R1, 1 -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R2, R2, [| _ |])
File "robustmatch.ml", lines 182-184, characters 4-23:
182 | ....match r1, r2, a with
183 | | R1, _, _ -> ()
184 | | _, R2, [||] -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R2, R2, [| _ |])
File "robustmatch.ml", lines 187-190, characters 4-20:
@ -129,7 +129,7 @@ File "robustmatch.ml", lines 187-190, characters 4-20:
188 | | _, R2, [||] -> ()
189 | | R1, _, 0 -> ()
190 | | R1, _, _ -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R2, R2, [| _ |])
File "robustmatch.ml", lines 200-203, characters 4-19:
@ -137,62 +137,62 @@ File "robustmatch.ml", lines 200-203, characters 4-19:
201 | | _, R2, [||] -> ()
202 | | R1, _, 0 -> ()
203 | | _, _, _ -> ()
Warning 4: this pattern-matching is fragile.
Warning 4 [fragile-match]: this pattern-matching is fragile.
It will remain exhaustive when constructors are added to type repr.
File "robustmatch.ml", lines 210-212, characters 4-27:
210 | ....match r1, r2, a with
211 | | R1, _, 'c' -> ()
212 | | _, R2, "coucou" -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, 'a')
File "robustmatch.ml", lines 219-221, characters 4-27:
219 | ....match r1, r2, a with
220 | | R1, _, `A -> ()
221 | | _, R2, "coucou" -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, `B)
File "robustmatch.ml", lines 228-230, characters 4-37:
228 | ....match r1, r2, a with
229 | | R1, _, (3, "") -> ()
230 | | _, R2, (1, "coucou", 'a') -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, (3, "*"))
File "robustmatch.ml", lines 239-241, characters 4-51:
239 | ....match r1, r2, a with
240 | | R1, _, { x = 3; y = "" } -> ()
241 | | _, R2, { a = 1; b = "coucou"; c = 'a' } -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, {x=3; y="*"})
File "robustmatch.ml", lines 244-246, characters 4-36:
244 | ....match r1, r2, a with
245 | | R2, _, { a = 1; b = "coucou"; c = 'a' } -> ()
246 | | _, R1, { x = 3; y = "" } -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R2, R2, {a=1; b="coucou"; c='b'})
File "robustmatch.ml", lines 253-255, characters 4-20:
253 | ....match r1, r2, a with
254 | | R1, _, (3, "") -> ()
255 | | _, R2, 1 -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, (3, "*"))
File "robustmatch.ml", lines 263-265, characters 4-20:
263 | ....match r1, r2, a with
264 | | R1, _, { x = 3; y = "" } -> ()
265 | | _, R2, 1 -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, {x=3; y="*"})
File "robustmatch.ml", lines 272-274, characters 4-20:
272 | ....match r1, r2, a with
273 | | R1, _, lazy 1 -> ()
274 | | _, R2, 1 -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R1, R1, lazy 0)
File "robustmatch.ml", lines 281-284, characters 4-24:
@ -200,6 +200,6 @@ File "robustmatch.ml", lines 281-284, characters 4-24:
282 | | R1, _, () -> ()
283 | | _, R2, "coucou" -> ()
284 | | _, R2, "foo" -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(R2, R2, "")

View File

@ -39,7 +39,7 @@ Lines 1-3, characters 0-20:
1 | match { x = assert false } with
2 | | { x = 3 } -> ()
3 | | { x = None } -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{x=Some _}
Exception: Assert_failure ("", 1, 12).
@ -54,7 +54,7 @@ Lines 1-3, characters 0-18:
1 | match { x = assert false } with
2 | | { x = None } -> ()
3 | | { x = "" } -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{x="*"}
Exception: Assert_failure ("", 1, 12).
@ -69,7 +69,7 @@ Lines 1-3, characters 0-18:
1 | match { x = assert false } with
2 | | { x = None } -> ()
3 | | { x = `X } -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{x=`AnyOtherTag}
Exception: Assert_failure ("", 1, 12).
@ -84,7 +84,7 @@ Lines 1-3, characters 0-17:
1 | match { x = assert false } with
2 | | { x = [||] } -> ()
3 | | { x = 3 } -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{x=0}
Exception: Assert_failure ("", 1, 12).
@ -99,7 +99,7 @@ Lines 1-3, characters 0-17:
1 | match { x = assert false } with
2 | | { x = `X } -> ()
3 | | { x = 3 } -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{x=0}
Exception: Assert_failure ("", 1, 12).
@ -114,7 +114,7 @@ Lines 1-3, characters 0-17:
1 | match { x = assert false } with
2 | | { x = `X "lol" } -> ()
3 | | { x = 3 } -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{x=0}
Exception: Assert_failure ("", 1, 12).
@ -131,7 +131,7 @@ Lines 1-4, characters 0-17:
2 | | { x = (2., "") } -> ()
3 | | { x = None } -> ()
4 | | { x = 3 } -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{x=0}
Exception: Assert_failure ("", 1, 12).

View File

@ -587,7 +587,7 @@ val let_not_principal : unit = ()
Line 3, characters 9-10:
3 | let+ A = A.A in
^
Warning 18: this type-based constructor disambiguation is not principal.
Warning 18 [not-principal]: this type-based constructor disambiguation is not principal.
val let_not_principal : unit = ()
|}];;
@ -616,7 +616,7 @@ val and_not_principal : A.t -> A.t -> unit = <fun>
Line 5, characters 11-12:
5 | and+ A = y in
^
Warning 18: this type-based constructor disambiguation is not principal.
Warning 18 [not-principal]: this type-based constructor disambiguation is not principal.
val and_not_principal : A.t -> A.t -> unit = <fun>
|}];;
@ -718,7 +718,7 @@ val bad_location : 'a GADT_ordering.is_point -> 'a -> int = <fun>
Line 4, characters 11-19:
4 | let+ Is_point = is_point
^^^^^^^^
Warning 18: typing this pattern requires considering GADT_ordering.point and a as equal.
Warning 18 [not-principal]: typing this pattern requires considering GADT_ordering.point and a as equal.
But the knowledge of these types is not principal.
Line 5, characters 13-14:
5 | and+ { x; y } = a in

View File

@ -1,7 +1,7 @@
Line 5, characters 58-64:
5 | let rec r = let rec x () = r and y () = x () in y () in r "oops";;
^^^^^^
Warning 20: this argument will not be used by the function.
Warning 20 [ignored-extra-argument]: this argument will not be used by the function.
Line 5, characters 12-52:
5 | let rec r = let rec x () = r and y () = x () in y () in r "oops";;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

View File

@ -1,7 +1,7 @@
Line 7, characters 15-17:
7 | let invalid = "\99" ;;
^^
Warning 14: illegal backslash escape in string.
Warning 14 [illegal-backslash]: illegal backslash escape in string.
val invalid : string = "\\99"
Line 1, characters 15-19:
1 | let invalid = "\999" ;;
@ -14,11 +14,11 @@ Error: Illegal backslash escape in string or character (\o777): o777 (=511) is o
Line 1, characters 15-17:
1 | let invalid = "\o77" ;;
^^
Warning 14: illegal backslash escape in string.
Warning 14 [illegal-backslash]: illegal backslash escape in string.
val invalid : string = "\\o77"
Line 1, characters 15-17:
1 | let invalid = "\o99" ;;
^^
Warning 14: illegal backslash escape in string.
Warning 14 [illegal-backslash]: illegal backslash escape in string.
val invalid : string = "\\o99"

View File

@ -25,11 +25,11 @@ Error: Illegal backslash escape in string or character (\u{01234567}): too many
Line 1, characters 21-23:
1 | let no_hex_digits = "\u{}" ;;
^^
Warning 14: illegal backslash escape in string.
Warning 14 [illegal-backslash]: illegal backslash escape in string.
val no_hex_digits : string = "\\u{}"
Line 1, characters 25-27:
1 | let illegal_hex_digit = "\u{u}" ;;
^^
Warning 14: illegal backslash escape in string.
Warning 14 [illegal-backslash]: illegal backslash escape in string.
val illegal_hex_digit : string = "\\u{u}"

View File

@ -21,7 +21,7 @@ Lines 8-11, characters 4-16:
9 | | exception e -> ()
10 | | Some false -> ()
11 | | None -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Some true
val test_match_exhaustiveness : unit -> unit = <fun>
@ -39,7 +39,7 @@ Lines 2-4, characters 4-30:
2 | ....match None with
3 | | Some false -> ()
4 | | None | exception _ -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Some true
val test_match_exhaustiveness_nest1 : unit -> unit = <fun>
@ -57,7 +57,7 @@ Lines 2-4, characters 4-16:
2 | ....match None with
3 | | Some false | exception _ -> ()
4 | | None -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Some true
val test_match_exhaustiveness_nest2 : unit -> unit = <fun>
@ -77,17 +77,17 @@ Lines 2-5, characters 4-30:
3 | | exception e -> ()
4 | | Some false | exception _ -> ()
5 | | None | exception _ -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Some true
Line 4, characters 29-30:
4 | | Some false | exception _ -> ()
^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
Line 5, characters 23-24:
5 | | None | exception _ -> ()
^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
val test_match_exhaustiveness_full : unit -> unit = <fun>
|}]
;;

View File

@ -86,7 +86,7 @@ end);;
Line 2, characters 0-9:
2 | open List
^^^^^^^^^
Error (warning 33): unused open Stdlib.List.
Error (warning 33 [unused-open]): unused open Stdlib.List.
|}];;
type unknown += Foo;;

View File

@ -1,9 +1,9 @@
File "aliases.ml", line 17, characters 12-13:
17 | module A' = A (* missing a.cmi *)
^
Warning 49: no cmi file was found in path for module A
Warning 49 [no-cmi-file]: no cmi file was found in path for module A
File "aliases.ml", line 18, characters 12-13:
18 | module B' = B (* broken b.cmi *)
^
Warning 49: no valid cmi file was found in path for module B. b.cmi
Warning 49 [no-cmi-file]: no valid cmi file was found in path for module B. b.cmi
is not a compiled interface

View File

@ -18,7 +18,7 @@ $\:$ int
$\?$let f <<x>> = () ;;
\end{camlinput}
\begin{camlwarn}
$\:$Warning 27: unused variable x.
$\:$Warning 27 [unused-var-strict]: unused variable x.
$\:$val f : 'a -> unit = <fun>
\end{camlwarn}
\end{caml}

View File

@ -1,4 +1,4 @@
File "tool-ocamlc-open-error.ml", line 1:
Warning 24: bad source file name: "Tool-ocamlc-open-error" is not a valid module name.
Warning 24 [bad-module-name]: bad source file name: "Tool-ocamlc-open-error" is not a valid module name.
File "command line argument: -open "F("", line 1, characters 1-2:
Error: Syntax error

View File

@ -3,7 +3,7 @@ val f : unit -> 'a = <fun>
Line 1, characters 11-15:
1 | let g () = f (); 1;;
^^^^
Warning 21: this statement never returns (or has an unsound type.)
Warning 21 [nonreturning-statement]: this statement never returns (or has an unsound type.)
val g : unit -> int = <fun>
Exception: Not_found.
Raised at f in file "//toplevel//", line 2, characters 11-26

View File

@ -3,7 +3,7 @@ type u = C of t
Line 1, characters 18-54:
1 | let print_t out = function A -> Format.fprintf out "A";;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
B
val print_t : Format.formatter -> t -> unit = <fun>

View File

@ -257,17 +257,17 @@ end
Line 2, characters 13-25:
2 | val x: int [@@alert 42]
^^^^^^^^^^^^
Warning 47: illegal payload for attribute 'alert'.
Warning 47 [attribute-payload]: illegal payload for attribute 'alert'.
Invalid payload
Line 3, characters 13-29:
3 | val y: int [@@alert bla 42]
^^^^^^^^^^^^^^^^
Warning 47: illegal payload for attribute 'alert'.
Warning 47 [attribute-payload]: illegal payload for attribute 'alert'.
Invalid payload
Line 4, characters 13-28:
4 | val z: int [@@alert "bla"]
^^^^^^^^^^^^^^^
Warning 47: illegal payload for attribute 'alert'.
Warning 47 [attribute-payload]: illegal payload for attribute 'alert'.
Ill-formed list of alert settings
module X : sig val x : int val y : int val z : int end
|}]

View File

@ -530,7 +530,7 @@ type t = [ `A of X.t | `B of X.s | `C of X.u ]
Line 1, characters 20-33:
1 | [@@@ocaml.ppwarning "Pp warning!"]
^^^^^^^^^^^^^
Warning 22: Pp warning!
Warning 22 [preprocessor]: Pp warning!
|}]
@ -541,11 +541,11 @@ let x = () [@ocaml.ppwarning "Pp warning 1!"]
Line 2, characters 24-39:
2 | [@@ocaml.ppwarning "Pp warning 2!"]
^^^^^^^^^^^^^^^
Warning 22: Pp warning 2!
Warning 22 [preprocessor]: Pp warning 2!
Line 1, characters 29-44:
1 | let x = () [@ocaml.ppwarning "Pp warning 1!"]
^^^^^^^^^^^^^^^
Warning 22: Pp warning 1!
Warning 22 [preprocessor]: Pp warning 1!
val x : unit = ()
|}]
@ -556,7 +556,7 @@ type t = unit
Line 2, characters 22-35:
2 | [@ocaml.ppwarning "Pp warning!"]
^^^^^^^^^^^^^
Warning 22: Pp warning!
Warning 22 [preprocessor]: Pp warning!
type t = unit
|}]
@ -574,7 +574,7 @@ end
Line 8, characters 22-36:
8 | [@@@ocaml.ppwarning "Pp warning2!"]
^^^^^^^^^^^^^^
Warning 22: Pp warning2!
Warning 22 [preprocessor]: Pp warning2!
module X : sig end
|}]
@ -586,7 +586,7 @@ let x =
Line 3, characters 23-38:
3 | [@ocaml.ppwarning "Pp warning 2!"]
^^^^^^^^^^^^^^^
Warning 22: Pp warning 2!
Warning 22 [preprocessor]: Pp warning 2!
val x : unit = ()
|}]
@ -599,11 +599,11 @@ type t =
Line 4, characters 21-36:
4 | [@@ocaml.ppwarning "Pp warning 3!"]
^^^^^^^^^^^^^^^
Warning 22: Pp warning 3!
Warning 22 [preprocessor]: Pp warning 3!
Line 3, characters 21-36:
3 | [@ocaml.ppwarning "Pp warning 2!"]
^^^^^^^^^^^^^^^
Warning 22: Pp warning 2!
Warning 22 [preprocessor]: Pp warning 2!
type t = unit
|}]
@ -613,11 +613,11 @@ let ([][@ocaml.ppwarning "XX"]) = []
Line 1, characters 25-29:
1 | let ([][@ocaml.ppwarning "XX"]) = []
^^^^
Warning 22: XX
Warning 22 [preprocessor]: XX
Line 1, characters 4-31:
1 | let ([][@ocaml.ppwarning "XX"]) = []
^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
_::_
|}]

View File

@ -242,7 +242,7 @@ type b = Unique
Line 7, characters 8-14:
7 | let x = Unique;;
^^^^^^
Warning 41: Unique belongs to several types: b M.s t a
Warning 41 [ambiguous-name]: Unique belongs to several types: b M.s t a
The first one was selected. Please disambiguate if this is wrong.
val x : b = Unique
|}]

View File

@ -306,7 +306,7 @@ type foo += Foo
Line 3, characters 8-26:
3 | let f = function Foo -> ()
^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
*extension*
Matching over values of extensible variant types (the *extension* above)
@ -327,7 +327,7 @@ Lines 1-4, characters 8-11:
2 | | [Foo] -> 1
3 | | _::_::_ -> 3
4 | | [] -> 2
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
*extension*::[]
Matching over values of extensible variant types (the *extension* above)
@ -350,7 +350,7 @@ let f = function IPair (i, j) -> Format.sprintf "(%d, %d)" i j ;;
Line 1, characters 8-62:
1 | let f = function IPair (i, j) -> Format.sprintf "(%d, %d)" i j ;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
*extension*
Matching over values of extensible variant types (the *extension* above)

View File

@ -15,7 +15,7 @@ type 'a ty = Int : int ty | Bool : bool ty
Lines 6-7, characters 2-13:
6 | ..match tag with
7 | | Bool -> x
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Int
val fbool : 't -> 't ty -> 't = <fun>
@ -31,7 +31,7 @@ let fint (type t) (x : t) (tag : t ty) =
Lines 2-3, characters 2-16:
2 | ..match tag with
3 | | Int -> x > 0
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Bool
val fint : 't -> 't ty -> bool = <fun>

View File

@ -17,7 +17,7 @@ Lines 7-9, characters 43-24:
7 | ...........................................function
8 | | One, One -> "two"
9 | | Two, Two -> "four"
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(One, Two)
module Add :

View File

@ -33,7 +33,7 @@ Lines 12-16, characters 2-36:
14 | | Leq, Int x, Int y -> Bool (x <= y)
15 | | Leq, Bool x, Bool y -> Bool (x <= y)
16 | | Add, Int x, Int y -> Int (x + y)
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(Eq, Int _, _)
val eval : ('a, 'b, 'c) binop -> 'a constant -> 'b constant -> 'c constant =

View File

@ -15,7 +15,7 @@ end;;
Lines 7-8, characters 47-21:
7 | ...............................................match l, r with
8 | | A, B -> "f A B"
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(A, A)
module F :
@ -42,7 +42,7 @@ end;;
Lines 10-11, characters 15-21:
10 | ...............match l, r with
11 | | A, B -> "f A B"
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(A, A)
module F :

View File

@ -28,7 +28,7 @@ module M : sig type s = private [> `A ] val eq : (s, [ `A | `B ]) t end
Lines 16-17, characters 39-16:
16 | .......................................function
17 | | Any -> "Any"
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Eq
val f : (M.s, [ `A | `B ]) t -> string = <fun>
@ -58,7 +58,7 @@ module N :
Lines 12-13, characters 49-16:
12 | .................................................function
13 | | Any -> "Any"
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Eq
val f : (N.s, < a : int; b : bool >) t -> string = <fun>

View File

@ -25,7 +25,7 @@ module M : sig type t = T val comp : (U.t, t) comp end
Line 16, characters 0-33:
16 | match M.comp with | Diff -> false;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Eq
Exception: Match_failure ("", 16, 0).
@ -48,7 +48,7 @@ module M : sig type t = { x : int; } val comp : (U.t, t) comp end
Line 11, characters 0-33:
11 | match M.comp with | Diff -> false;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Eq
Exception: Match_failure ("", 11, 0).

View File

@ -24,7 +24,7 @@ type (_, _) t = A : ('a, 'a) t | B : string -> ('a, 'b) t
Lines 8-9, characters 52-13:
8 | ....................................................function
9 | | B s -> s
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
A
module M :

View File

@ -20,7 +20,7 @@ type (_, _) eqp = Y : ('a, 'a) eqp | N : string -> ('a, 'b) eqp
Line 2, characters 36-66:
2 | let f : ('a list, 'a) eqp -> unit = function N s -> print_string s;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Y
val f : ('a list, 'a) eqp -> unit = <fun>

View File

@ -14,7 +14,7 @@ type (_, _) t =
Line 5, characters 9-43:
5 | let get1 (Cons (x, _) : (_ * 'a, 'a) t) = x ;; (* warn, cf PR#6993 *)
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Nil
val get1 : ('b * 'a, 'a) t -> 'b = <fun>

View File

@ -11,7 +11,7 @@ type 'a t
Line 3, characters 15-40:
3 | let f (type a) (Neq n : (a, a t) eq) = n;; (* warn! *)
^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Eq
val f : ('a, 'a t) eq -> int = <fun>
@ -24,7 +24,7 @@ end;;
Line 2, characters 16-43:
2 | let f (type a) (Neq n : (a, a T.t) eq) = n (* warn! *)
^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Eq
module F :

View File

@ -14,7 +14,7 @@ type +'a t = T : [< `Conj of 'a & sub | `Other of string ] -> 'a t
Line 4, characters 6-47:
4 | let f (T (`Other msg) : s t) = print_string msg;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
T (`Conj _)
val f : s t -> unit = <fun>
@ -42,7 +42,7 @@ module M :
Line 11, characters 12-59:
11 | let () = M.(match x with T (`Other msg) -> print_string msg);; (* warn *)
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
T (`Conj _)
Exception: Match_failure ("", 11, 12).
@ -74,7 +74,7 @@ module M :
Line 13, characters 21-57:
13 | let () = M.(e { ex = fun (`Other msg) -> print_string msg });; (* warn *)
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
`Conj _
Exception: Match_failure ("", 13, 21).

View File

@ -24,7 +24,7 @@ let f (* : filled either -> string *) =
Line 2, characters 2-28:
2 | fun (Either (Y a, N)) -> a;;
^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Either (N, Y _)
val f : filled either -> string = <fun>

View File

@ -24,7 +24,7 @@ let f : [`L of (s, t) eql | `R of silly] -> 'a =
Line 2, characters 2-30:
2 | function `R {silly} -> silly
^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
`L Refl
val f : [ `L of (s, t) eql | `R of silly ] -> 'a = <fun>

View File

@ -36,7 +36,7 @@ Lines 4-8, characters 2-18:
6 | | MAB, _, A -> 2
7 | | _, AB, B -> 3
8 | | _, MAB, B -> 4
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(AB, MAB, A)
val f : 'x M.t -> 'x M.t -> 'x -> int = <fun>
@ -137,7 +137,7 @@ let f (type x) (t1 : x t) (t2 : x t) (x : x) =
Line 7, characters 4-22:
7 | | _, AB, { a = _ } -> 3
^^^^^^^^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
val f : 'x M.t -> 'x M.t -> 'x -> int = <fun>
|}]
@ -167,7 +167,7 @@ Lines 9-11, characters 2-37:
9 | ..match a, a_or_b, x with
10 | | Not_A, A_or_B, `B i -> print_int i
11 | | _, A_or_B, `A s -> print_string s
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(A, A_or_B, `B _)
val f : 'x a -> 'x a_or_b -> 'x -> unit = <fun>
@ -198,7 +198,7 @@ Lines 9-11, characters 2-18:
9 | ..match b, x, y with
10 | | B, `B String_option, Some s -> print_string s
11 | | A, `A, _ -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(B, `B String_option, None)
val f : ('x, 'y ty) b -> 'x -> 'y -> unit = <fun>
@ -218,7 +218,7 @@ type 'a a = private [< `A of 'a ]
Line 2, characters 18-44:
2 | let f (x : _ a) = match x with `A None -> ();;
^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
`A (Some _)
val f : 'a option a -> unit = <fun>
@ -229,7 +229,7 @@ let f (x : [> `A] a) = match x with `A `B -> ();;
Line 1, characters 23-47:
1 | let f (x : [> `A] a) = match x with `A `B -> ();;
^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
`A `A
val f : [< `A | `B > `A ] a -> unit = <fun>

View File

@ -21,7 +21,7 @@ let f = function Sigma (M, A) -> ();;
Line 1, characters 8-35:
1 | let f = function Sigma (M, A) -> ();;
^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Sigma (M, B)
val f : dyn -> unit = <fun>
@ -46,12 +46,12 @@ val f : 'a t -> 'a -> int = <fun>
Line 4, characters 4-10:
4 | | IntLit, n -> n+1
^^^^^^
Warning 18: typing this pattern requires considering int and a as equal.
Warning 18 [not-principal]: typing this pattern requires considering int and a as equal.
But the knowledge of these types is not principal.
Line 5, characters 4-11:
5 | | BoolLit, b -> 1
^^^^^^^
Warning 18: typing this pattern requires considering bool and a as equal.
Warning 18 [not-principal]: typing this pattern requires considering bool and a as equal.
But the knowledge of these types is not principal.
val f : 'a t -> 'a -> int = <fun>
|}]
@ -68,7 +68,7 @@ val f : 'a t -> 'a -> int = <fun>
Line 4, characters 4-10:
4 | | IntLit, n -> n+1
^^^^^^
Warning 18: typing this pattern requires considering int and a as equal.
Warning 18 [not-principal]: typing this pattern requires considering int and a as equal.
But the knowledge of these types is not principal.
val f : 'a t -> 'a -> int = <fun>
|}]
@ -136,7 +136,7 @@ val f1 : unit ab M.t -> bool = <fun>
Line 4, characters 4-7:
4 | | MAB -> false;;
^^^
Warning 18: typing this pattern requires considering unit M.mab and unit ab as equal.
Warning 18 [not-principal]: typing this pattern requires considering unit M.mab and unit ab as equal.
But the knowledge of these types is not principal.
val f1 : unit ab M.t -> bool = <fun>
|}]
@ -152,12 +152,12 @@ val f2 : 'x M.t -> bool = <fun>
Line 4, characters 4-6:
4 | | AB -> true
^^
Warning 18: typing this pattern requires considering unit ab and x as equal.
Warning 18 [not-principal]: typing this pattern requires considering unit ab and x as equal.
But the knowledge of these types is not principal.
Line 5, characters 4-7:
5 | | MAB -> false;;
^^^
Warning 18: typing this pattern requires considering unit M.mab and x as equal.
Warning 18 [not-principal]: typing this pattern requires considering unit M.mab and x as equal.
But the knowledge of these types is not principal.
val f2 : 'x M.t -> bool = <fun>
|}]
@ -174,7 +174,7 @@ val f3 : unit ab M.t -> bool = <fun>
Line 5, characters 4-7:
5 | | MAB -> false;;
^^^
Warning 18: typing this pattern requires considering unit M.mab and unit ab as equal.
Warning 18 [not-principal]: typing this pattern requires considering unit M.mab and unit ab as equal.
But the knowledge of these types is not principal.
val f3 : unit ab M.t -> bool = <fun>
|}]
@ -201,7 +201,7 @@ val g2 : ('x, int option) eq -> 'x -> int option = <fun>
Line 3, characters 7-11:
3 | let Refl = e in x;;
^^^^
Warning 18: typing this pattern requires considering x and int option as equal.
Warning 18 [not-principal]: typing this pattern requires considering x and int option as equal.
But the knowledge of these types is not principal.
val g2 : ('x, int option) eq -> 'x -> int option = <fun>
|}]
@ -232,7 +232,7 @@ let () =
Line 3, characters 27-28:
3 | | [ { a = 3; _ } ; { b = F; _ }] -> ()
^
Warning 18: typing this pattern requires considering Foo.t and int as equal.
Warning 18 [not-principal]: typing this pattern requires considering Foo.t and int as equal.
But the knowledge of these types is not principal.
|}]
@ -267,7 +267,7 @@ let () =
Line 3, characters 26-31:
3 | | [ { a = 3; _ }; { b = Refl3 ; _ }] -> ()
^^^^^
Warning 18: typing this pattern requires considering int and Foo.t as equal.
Warning 18 [not-principal]: typing this pattern requires considering int and Foo.t as equal.
But the knowledge of these types is not principal.
|}]
@ -281,7 +281,7 @@ let () =
Line 3, characters 12-17:
3 | | [ { b = Refl3 ; _ }; { a = 3; _ } ] -> ()
^^^^^
Warning 18: typing this pattern requires considering int and Foo.t as equal.
Warning 18 [not-principal]: typing this pattern requires considering int and Foo.t as equal.
But the knowledge of these types is not principal.
|}]
@ -302,7 +302,7 @@ let () =
Line 3, characters 26-31:
3 | | [ { a = 3; _ }; { b = Refl3 ; _ }] -> ()
^^^^^
Warning 18: typing this pattern requires considering int and Foo.t as equal.
Warning 18 [not-principal]: typing this pattern requires considering int and Foo.t as equal.
But the knowledge of these types is not principal.
|}]
@ -315,7 +315,7 @@ let () =
Line 3, characters 12-17:
3 | | [ { b = Refl3 ; _ }; { a = 3; _ } ] -> ()
^^^^^
Warning 18: typing this pattern requires considering int and Foo.t as equal.
Warning 18 [not-principal]: typing this pattern requires considering int and Foo.t as equal.
But the knowledge of these types is not principal.
|}]
@ -347,7 +347,7 @@ val foo : M.t foo -> M.t = <fun>
Line 3, characters 18-23:
3 | | { x = x; eq = Refl3 } -> x
^^^^^
Warning 18: typing this pattern requires considering M.t and N.t as equal.
Warning 18 [not-principal]: typing this pattern requires considering M.t and N.t as equal.
But the knowledge of these types is not principal.
val foo : M.t foo -> M.t = <fun>
|}]
@ -362,7 +362,7 @@ val foo : int foo -> int = <fun>
Line 3, characters 26-31:
3 | | { x = (x : int); eq = Refl3 } -> x
^^^^^
Warning 18: typing this pattern requires considering M.t and int as equal.
Warning 18 [not-principal]: typing this pattern requires considering M.t and int as equal.
But the knowledge of these types is not principal.
val foo : int foo -> int = <fun>
|}]
@ -383,7 +383,7 @@ Error: This pattern matches values of type N.t foo
Line 3, characters 26-31:
3 | | { x = (x : N.t); eq = Refl3 } -> x
^^^^^
Warning 18: typing this pattern requires considering M.t and N.t as equal.
Warning 18 [not-principal]: typing this pattern requires considering M.t and N.t as equal.
But the knowledge of these types is not principal.
Line 3, characters 4-33:
3 | | { x = (x : N.t); eq = Refl3 } -> x
@ -404,7 +404,7 @@ val foo : string foo -> string = <fun>
Line 3, characters 29-34:
3 | | { x = (x : string); eq = Refl3 } -> x
^^^^^
Warning 18: typing this pattern requires considering M.t and string as equal.
Warning 18 [not-principal]: typing this pattern requires considering M.t and string as equal.
But the knowledge of these types is not principal.
val foo : string foo -> string = <fun>
|}]

View File

@ -106,14 +106,14 @@ module Nonexhaustive =
Lines 11-12, characters 6-19:
11 | ......function
12 | | C2 x -> x
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
C1 _
Lines 24-26, characters 6-30:
24 | ......function
25 | | Foo _ , Foo _ -> true
26 | | Bar _, Bar _ -> true
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(Foo _, Bar _)
module Nonexhaustive :
@ -160,13 +160,13 @@ end;;
Line 2, characters 10-18:
2 | class c (Some x) = object method x : int = x end
^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
None
Line 4, characters 10-18:
4 | class d (Just x) = object method x : int = x end
^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Nothing
module PR6862 :
@ -195,7 +195,7 @@ end;;
Line 4, characters 43-44:
4 | let g : int t -> int = function I -> 1 | _ -> 2 (* warn *)
^
Warning 56: this match case is unreachable.
Warning 56 [unreachable-case]: this match case is unreachable.
Consider replacing it with a refutation case '<pat> -> .'
module PR6220 :
sig
@ -263,7 +263,7 @@ end;;
Lines 8-9, characters 4-33:
8 | ....match x with
9 | | String s -> print_endline s.................
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Any
module PR6801 :
@ -918,7 +918,7 @@ Lines 2-8, characters 2-16:
6 | | TE TC, D [|1.0|] -> 14
7 | | TA, D 0 -> -1
8 | | TA, D z -> z
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(TE TC, D [| 0. |])
val f : 'a ty -> 'a t -> int = <fun>
@ -982,7 +982,7 @@ Lines 4-10, characters 2-29:
8 | | {left=TE TC; right=D [|1.0|]} -> 14
9 | | {left=TA; right=D 0} -> -1
10 | | {left=TA; right=D z} -> z
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{left=TE TC; right=D [| 0. |]}
val f : 'a ty -> 'a t -> int = <fun>

View File

@ -60,7 +60,7 @@ Lines 5-7, characters 39-23:
5 | .......................................function
6 | | BoolLit, false -> false
7 | | IntLit , 6 -> false
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(BoolLit, true)
val check : 's t * 's -> bool = <fun>
@ -78,7 +78,7 @@ Lines 3-5, characters 45-38:
3 | .............................................function
4 | | {fst = BoolLit; snd = false} -> false
5 | | {fst = IntLit ; snd = 6} -> false
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{fst=BoolLit; snd=true}
val check : ('s t, 's) pair -> bool = <fun>

View File

@ -72,7 +72,7 @@ Lines 5-7, characters 4-7:
5 | ....begin match x with
6 | | `A -> ()
7 | end
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
`B
val f : t -> unit = <fun>
@ -128,7 +128,7 @@ Lines 5-7, characters 4-7:
5 | ....begin match x with
6 | | `A -> ()
7 | end
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
`B
val f : t -> unit = <fun>
@ -148,7 +148,7 @@ Lines 5-7, characters 4-7:
5 | ....begin match x with
6 | | `A -> ()
7 | end
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
`B
val f : t -> unit = <fun>

View File

@ -134,7 +134,7 @@ module PR6505b :
Line 6, characters 23-57:
6 | let () = print_endline (match PR6505b.x with `Bar s -> s);; (* fails *)
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
`Foo _
Exception: Match_failure ("", 6, 23).

View File

@ -37,7 +37,7 @@ let after_a =
Line 3, characters 2-20:
3 | { x with lbl = 4 }
^^^^^^^^^^^^^^^^^^
Warning 23: all the fields are explicitly listed in this record:
Warning 23 [useless-record-with]: all the fields are explicitly listed in this record:
the 'with' clause is useless.
val after_a : M.r = {M.lbl = 4}
|}]
@ -52,7 +52,7 @@ val b : unit = ()
Line 3, characters 7-18:
3 | x := { lbl = 4 }
^^^^^^^^^^^
Warning 18: this type-based record disambiguation is not principal.
Warning 18 [not-principal]: this type-based record disambiguation is not principal.
val b : unit = ()
|}]
@ -110,17 +110,17 @@ let h x =
Line 4, characters 4-15:
4 | | { lbl = _ } -> ()
^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
val h : M.r -> unit = <fun>
|}, Principal{|
Line 4, characters 4-15:
4 | | { lbl = _ } -> ()
^^^^^^^^^^^
Warning 18: this type-based record disambiguation is not principal.
Warning 18 [not-principal]: this type-based record disambiguation is not principal.
Line 4, characters 4-15:
4 | | { lbl = _ } -> ()
^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
val h : M.r -> unit = <fun>
|}]
@ -145,17 +145,17 @@ let j x =
Line 4, characters 4-15:
4 | | { lbl = _ } -> ()
^^^^^^^^^^^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
val j : M.r -> unit = <fun>
|}, Principal{|
Line 4, characters 4-15:
4 | | { lbl = _ } -> ()
^^^^^^^^^^^
Warning 18: this type-based record disambiguation is not principal.
Warning 18 [not-principal]: this type-based record disambiguation is not principal.
Line 4, characters 4-15:
4 | | { lbl = _ } -> ()
^^^^^^^^^^^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
val j : M.r -> unit = <fun>
|}]
@ -199,17 +199,17 @@ let n x =
Line 4, characters 4-30:
4 | | { contents = { lbl = _ } } -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
val n : M.r ref -> unit = <fun>
|}, Principal{|
Line 4, characters 17-28:
4 | | { contents = { lbl = _ } } -> ()
^^^^^^^^^^^
Warning 18: this type-based record disambiguation is not principal.
Warning 18 [not-principal]: this type-based record disambiguation is not principal.
Line 4, characters 4-30:
4 | | { contents = { lbl = _ } } -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
val n : M.r ref -> unit = <fun>
|}]
@ -234,17 +234,17 @@ let p x =
Line 4, characters 4-30:
4 | | { contents = { lbl = _ } } -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
val p : M.r ref -> unit = <fun>
|}, Principal{|
Line 4, characters 17-28:
4 | | { contents = { lbl = _ } } -> ()
^^^^^^^^^^^
Warning 18: this type-based record disambiguation is not principal.
Warning 18 [not-principal]: this type-based record disambiguation is not principal.
Line 4, characters 4-30:
4 | | { contents = { lbl = _ } } -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
val p : M.r ref -> unit = <fun>
|}]
@ -280,7 +280,7 @@ val s : M.r ref -> unit = <fun>
Line 4, characters 9-20:
4 | x := { lbl = 4 }
^^^^^^^^^^^
Warning 18: this type-based record disambiguation is not principal.
Warning 18 [not-principal]: this type-based record disambiguation is not principal.
val s : M.r ref -> unit = <fun>
|}]
@ -294,7 +294,7 @@ val t : M.r ref -> unit = <fun>
Line 3, characters 9-20:
3 | x := { lbl = 4 }
^^^^^^^^^^^
Warning 18: this type-based record disambiguation is not principal.
Warning 18 [not-principal]: this type-based record disambiguation is not principal.
val t : M.r ref -> unit = <fun>
|}]
@ -344,7 +344,7 @@ val b : unit = ()
Line 3, characters 7-8:
3 | x := B
^
Warning 18: this type-based constructor disambiguation is not principal.
Warning 18 [not-principal]: this type-based constructor disambiguation is not principal.
val b : unit = ()
|}]
@ -388,7 +388,7 @@ val h : M.t -> unit = <fun>
Line 4, characters 4-5:
4 | | B -> ()
^
Warning 18: this type-based constructor disambiguation is not principal.
Warning 18 [not-principal]: this type-based constructor disambiguation is not principal.
val h : M.t -> unit = <fun>
|}]
@ -415,7 +415,7 @@ val j : M.t -> unit = <fun>
Line 4, characters 4-5:
4 | | B -> ()
^
Warning 18: this type-based constructor disambiguation is not principal.
Warning 18 [not-principal]: this type-based constructor disambiguation is not principal.
val j : M.t -> unit = <fun>
|}]
@ -459,17 +459,17 @@ let n x =
Line 4, characters 4-20:
4 | | { contents = A } -> ()
^^^^^^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
val n : M.t ref -> unit = <fun>
|}, Principal{|
Line 4, characters 17-18:
4 | | { contents = A } -> ()
^
Warning 18: this type-based constructor disambiguation is not principal.
Warning 18 [not-principal]: this type-based constructor disambiguation is not principal.
Line 4, characters 4-20:
4 | | { contents = A } -> ()
^^^^^^^^^^^^^^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
val n : M.t ref -> unit = <fun>
|}]
@ -494,17 +494,17 @@ let p x =
Line 4, characters 4-20:
4 | | { contents = A } -> ()
^^^^^^^^^^^^^^^^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
val p : M.t ref -> unit = <fun>
|}, Principal{|
Line 4, characters 17-18:
4 | | { contents = A } -> ()
^
Warning 18: this type-based constructor disambiguation is not principal.
Warning 18 [not-principal]: this type-based constructor disambiguation is not principal.
Line 4, characters 4-20:
4 | | { contents = A } -> ()
^^^^^^^^^^^^^^^^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
val p : M.t ref -> unit = <fun>
|}]
@ -531,7 +531,7 @@ val s : M.t ref -> unit = <fun>
Line 4, characters 9-10:
4 | x := A
^
Warning 18: this type-based constructor disambiguation is not principal.
Warning 18 [not-principal]: this type-based constructor disambiguation is not principal.
val s : M.t ref -> unit = <fun>
|}]
@ -544,7 +544,7 @@ Lines 1-3, characters 8-10:
1 | ........function
2 | | ({ contents = M.A } : M.t ref) as x ->
3 | x := B
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{contents=B}
val t : M.t ref -> unit = <fun>
@ -552,12 +552,12 @@ val t : M.t ref -> unit = <fun>
Line 3, characters 9-10:
3 | x := B
^
Warning 18: this type-based constructor disambiguation is not principal.
Warning 18 [not-principal]: this type-based constructor disambiguation is not principal.
Lines 1-3, characters 8-10:
1 | ........function
2 | | ({ contents = M.A } : M.t ref) as x ->
3 | x := B
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{contents=B}
val t : M.t ref -> unit = <fun>

View File

@ -57,7 +57,7 @@ module Runner : sig val ac : f:((unit, 'a, unit) t -> unit) -> unit end
Lines 16-17, characters 8-18:
16 | ........match abc with
17 | | A _ -> 1
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
C ()
val f : unit -> unit = <fun>
@ -72,7 +72,7 @@ type 'b t = A | B of 'b | C
Line 3, characters 22-42:
3 | let g (x:nothing t) = match x with A -> ()
^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
C
val g : nothing t -> unit = <fun>

View File

@ -309,7 +309,7 @@ val d : dyn = Dyn (Vec (Vec Int), <poly>)
Line 47, characters 4-11:
47 | let Some v' = undyn int_vec_vec d
^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
None
val v' : int Vec.t Vec.t = <abstr>
@ -340,7 +340,7 @@ val coe : ('a, 'b) eq -> 'a ty -> 'b ty = <fun>
Line 17, characters 2-30:
17 | let Vec Int = vec_ty in Refl
^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Vec (Vec Int)
val eq_int_any : (int, 'a) eq = Refl

View File

@ -10,7 +10,7 @@ val f : x:int -> int = <fun>
Line 2, characters 5-6:
2 | f ?x:0;;
^
Warning 43: the label x is not optional.
Warning 43 [nonoptional-label]: the label x is not optional.
- : int = 1
|}];;
@ -65,7 +65,7 @@ val f : (?x:int -> unit -> int) -> int = <fun>
Line 1, characters 51-52:
1 | let f g = ignore (g : ?x:int -> unit -> int); g ~x:3 () ;;
^
Warning 18: using an optional argument here is not principal.
Warning 18 [not-principal]: using an optional argument here is not principal.
val f : (?x:int -> unit -> int) -> int = <fun>
|}];;
@ -76,7 +76,7 @@ val f : (?x:int -> unit -> int) -> int = <fun>
Line 1, characters 46-47:
1 | let f g = ignore (g : ?x:int -> unit -> int); g ();;
^
Warning 19: eliminated optional argument without principality.
Warning 19 [non-principal-labels]: eliminated optional argument without principality.
val f : (?x:int -> unit -> int) -> int = <fun>
|}];;
@ -87,6 +87,6 @@ val f : (x:int -> unit -> int) -> x:int -> int = <fun>
Line 1, characters 45-46:
1 | let f g = ignore (g : x:int -> unit -> int); g ();;
^
Warning 19: commuted an argument without principality.
Warning 19 [non-principal-labels]: commuted an argument without principality.
val f : (x:int -> unit -> int) -> x:int -> int = <fun>
|}];;

View File

@ -37,7 +37,7 @@ let f (x : [< `A | `B]) = match x with `A | `B | `C -> 0;; (* warn *)
Line 1, characters 49-51:
1 | let f (x : [< `A | `B]) = match x with `A | `B | `C -> 0;; (* warn *)
^^
Warning 12: this sub-pattern is unused.
Warning 12 [redundant-subpat]: this sub-pattern is unused.
val f : [< `A | `B ] -> int = <fun>
|}];;
let f (x : [`A | `B]) = match x with `A | `B | `C -> 0;; (* fail *)
@ -73,31 +73,31 @@ type t = A | B
Line 9, characters 0-41:
9 | function (`A|`B), _ -> 0 | _,(`A|`B) -> 1;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(`AnyOtherTag, `AnyOtherTag)
- : [> `A | `B ] * [> `A | `B ] -> int = <fun>
Line 10, characters 0-29:
10 | function `B,1 -> 1 | _,1 -> 2;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(_, 0)
Line 10, characters 21-24:
10 | function `B,1 -> 1 | _,1 -> 2;;
^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
- : [< `B ] * int -> int = <fun>
Line 11, characters 0-29:
11 | function 1,`B -> 1 | 1,_ -> 2;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(0, _)
Line 11, characters 21-24:
11 | function 1,`B -> 1 | 1,_ -> 2;;
^^^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
- : int * [< `B ] -> int = <fun>
|}];;
@ -138,7 +138,7 @@ type t = private [> `A of string ]
Line 2, characters 0-24:
2 | function (`A x : t) -> x;;
^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
`<some private tag>
- : t -> string = <fun>
@ -149,7 +149,7 @@ let f = function `AnyOtherTag, _ -> 1 | _, (`AnyOtherTag|`AnyOtherTag') -> 2;;
Line 1, characters 8-76:
1 | let f = function `AnyOtherTag, _ -> 1 | _, (`AnyOtherTag|`AnyOtherTag') -> 2;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(`AnyOtherTag', `AnyOtherTag'')
val f : [> `AnyOtherTag ] * [> `AnyOtherTag | `AnyOtherTag' ] -> int = <fun>

View File

@ -385,7 +385,7 @@ module Foo : sig type info = { doc : unit; } type t = { info : info; } end
Line 5, characters 38-41:
5 | let add_extra_info arg = arg.Foo.info.doc
^^^
Warning 40: doc was selected from type Foo.info.
Warning 40 [name-out-of-scope]: doc was selected from type Foo.info.
It is not visible in the current scope, and will not
be selected if the type becomes unknown.
val add_extra_info : Foo.t -> unit = <fun>
@ -407,7 +407,7 @@ module Bar : sig end
Line 8, characters 38-41:
8 | let add_extra_info arg = arg.Foo.info.doc
^^^
Warning 40: doc was selected from type Bar/2.info.
Warning 40 [name-out-of-scope]: doc was selected from type Bar/2.info.
It is not visible in the current scope, and will not
be selected if the type becomes unknown.
val add_extra_info : Foo.t -> unit = <fun>

View File

@ -8,7 +8,7 @@ let rec x = [| x |]; 1.;;
Line 1, characters 12-19:
1 | let rec x = [| x |]; 1.;;
^^^^^^^
Warning 10: this expression should have type unit.
Warning 10 [non-unit-statement]: this expression should have type unit.
Line 1, characters 12-23:
1 | let rec x = [| x |]; 1.;;
^^^^^^^^^^^

View File

@ -171,7 +171,7 @@ let r = { (assert false) with contents = 1 } ;;
Line 1, characters 8-44:
1 | let r = { (assert false) with contents = 1 } ;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 23: all the fields are explicitly listed in this record:
Warning 23 [useless-record-with]: all the fields are explicitly listed in this record:
the 'with' clause is useless.
Exception: Assert_failure ("", 1, 10).
|}]

View File

@ -1,6 +1,6 @@
File "pr7284_bad.ml", line 35, characters 30-62:
35 | let f : X.v1 wit -> unit = function V1 s -> print_endline s
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Error (warning 8): this pattern-matching is not exhaustive.
Error (warning 8 [partial-match]): this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
V2 _

View File

@ -289,7 +289,7 @@ end;;
Line 3, characters 10-27:
3 | inherit printable_point y as super
^^^^^^^^^^^^^^^^^
Warning 13: the following instance variables are overridden by the class printable_point :
Warning 13 [instance-variable-override]: the following instance variables are overridden by the class printable_point :
x
The behaviour changed in ocaml 3.10 (previous behaviour was hiding.)
class printable_color_point :
@ -618,7 +618,7 @@ let pr l =
Line 2, characters 2-69:
2 | List.map (fun c -> Format.print_int c#x; Format.print_string " ") l;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 10: this expression should have type unit.
Warning 10 [non-unit-statement]: this expression should have type unit.
val pr : < x : int; .. > list -> unit = <fun>
|}];;
let l = [new int_comparable 5; (new int_comparable3 2 :> int_comparable);

View File

@ -472,24 +472,24 @@ end;;
Line 3, characters 10-13:
3 | inherit c 5
^^^
Warning 13: the following instance variables are overridden by the class c :
Warning 13 [instance-variable-override]: the following instance variables are overridden by the class c :
x
The behaviour changed in ocaml 3.10 (previous behaviour was hiding.)
Line 4, characters 6-7:
4 | val y = 3
^
Warning 13: the instance variable y is overridden.
Warning 13 [instance-variable-override]: the instance variable y is overridden.
The behaviour changed in ocaml 3.10 (previous behaviour was hiding.)
Line 6, characters 10-13:
6 | inherit d 7
^^^
Warning 13: the following instance variables are overridden by the class d :
Warning 13 [instance-variable-override]: the following instance variables are overridden by the class d :
t z
The behaviour changed in ocaml 3.10 (previous behaviour was hiding.)
Line 7, characters 6-7:
7 | val u = 3
^
Warning 13: the instance variable u is overridden.
Warning 13 [instance-variable-override]: the instance variable u is overridden.
The behaviour changed in ocaml 3.10 (previous behaviour was hiding.)
class e :
unit ->
@ -791,7 +791,7 @@ fun (x : 'a t) -> (x : 'a); ();;
Line 1, characters 18-26:
1 | fun (x : 'a t) -> (x : 'a); ();;
^^^^^^^^
Warning 10: this expression should have type unit.
Warning 10 [non-unit-statement]: this expression should have type unit.
- : ('a t as 'a) t -> unit = <fun>
|}];;

View File

@ -1,5 +1,5 @@
File "pervasives_leitmotiv.ml", line 1:
Warning 63: The printed interface differs from the inferred interface.
Warning 63 [erroneous-printed-signature]: The printed interface differs from the inferred interface.
The inferred interface contained items which could not be printed
properly due to name collisions between identifiers.
File "pervasives_leitmotiv.ml", lines 10-12, characters 0-3:

View File

@ -1,5 +1,5 @@
File "pr4791.ml", line 1:
Warning 63: The printed interface differs from the inferred interface.
Warning 63 [erroneous-printed-signature]: The printed interface differs from the inferred interface.
The inferred interface contained items which could not be printed
properly due to name collisions between identifiers.
File "pr4791.ml", line 11, characters 2-12:

View File

@ -1,5 +1,5 @@
File "pr6323.ml", line 1:
Warning 63: The printed interface differs from the inferred interface.
Warning 63 [erroneous-printed-signature]: The printed interface differs from the inferred interface.
The inferred interface contained items which could not be printed
properly due to name collisions between identifiers.
File "pr6323.ml", line 15, characters 2-24:

View File

@ -1,5 +1,5 @@
File "pr7402.ml", line 1:
Warning 63: The printed interface differs from the inferred interface.
Warning 63 [erroneous-printed-signature]: The printed interface differs from the inferred interface.
The inferred interface contained items which could not be printed
properly due to name collisions between identifiers.
File "pr7402.ml", lines 14-16, characters 0-5:

View File

@ -52,7 +52,7 @@ Lines 1-4, characters 0-24:
2 | | {pv=[]} -> "OK"
3 | | {pv=5::_} -> "int"
4 | | {pv=true::_} -> "bool"
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{pv=false::_}
- : string = "OK"
@ -69,7 +69,7 @@ Lines 1-4, characters 0-20:
2 | | {pv=[]} -> "OK"
3 | | {pv=true::_} -> "bool"
4 | | {pv=5::_} -> "int"
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{pv=0::_}
- : string = "OK"
@ -304,7 +304,7 @@ class ['a] ostream1 :
Line 8, characters 4-16:
8 | self#tl#fold ~f ~init:(f self#hd init)
^^^^^^^^^^^^
Warning 18: this use of a polymorphic method is not principal.
Warning 18 [not-principal]: this use of a polymorphic method is not principal.
class ['a] ostream1 :
hd:'a ->
tl:'b ->
@ -1089,7 +1089,7 @@ val f : unit -> c = <fun>
Line 4, characters 11-60:
4 | let f () = object method private n = 1 method m = {<>}#n end;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 15: the following private methods were made public implicitly:
Warning 15 [implicit-public-methods]: the following private methods were made public implicitly:
n.
val f : unit -> < m : int; n : int > = <fun>
Line 5, characters 11-56:
@ -1259,19 +1259,19 @@ val f : < m : 'a. 'a -> 'a > -> < m : 'a. 'a -> 'a > = <fun>
Line 2, characters 9-16:
2 | fun x -> (f x)#m;; (* Warning 18 *)
^^^^^^^
Warning 18: this use of a polymorphic method is not principal.
Warning 18 [not-principal]: this use of a polymorphic method is not principal.
- : < m : 'a. 'a -> 'a > -> 'b -> 'b = <fun>
val f : < m : 'a. 'a -> 'a > * 'b -> < m : 'a. 'a -> 'a > = <fun>
Line 4, characters 9-20:
4 | fun x -> (f (x,x))#m;; (* Warning 18 *)
^^^^^^^^^^^
Warning 18: this use of a polymorphic method is not principal.
Warning 18 [not-principal]: this use of a polymorphic method is not principal.
- : < m : 'a. 'a -> 'a > -> 'b -> 'b = <fun>
val f : < m : 'a. 'a -> 'a > -> < m : 'a. 'a -> 'a > array = <fun>
Line 6, characters 9-20:
6 | fun x -> (f x).(0)#m;; (* Warning 18 *)
^^^^^^^^^^^
Warning 18: this use of a polymorphic method is not principal.
Warning 18 [not-principal]: this use of a polymorphic method is not principal.
- : < m : 'a. 'a -> 'a > -> 'b -> 'b = <fun>
|}];;
@ -1300,12 +1300,12 @@ val just : 'a option -> 'a = <fun>
Line 4, characters 42-62:
4 | let f x = let l = [Some x; (None : u)] in (just(List.hd l))#id;;
^^^^^^^^^^^^^^^^^^^^
Warning 18: this use of a polymorphic method is not principal.
Warning 18 [not-principal]: this use of a polymorphic method is not principal.
val f : c -> 'a -> 'a = <fun>
Line 7, characters 36-47:
7 | let x = List.hd [Some x; none] in (just x)#id;;
^^^^^^^^^^^
Warning 18: this use of a polymorphic method is not principal.
Warning 18 [not-principal]: this use of a polymorphic method is not principal.
val g : c -> 'a -> 'a = <fun>
val h : < id : 'a; .. > -> 'a = <fun>
|}];;

View File

@ -40,7 +40,7 @@ let f x =
Lines 4-5, characters 2-38:
4 | ..match [] with
5 | | _::_ -> (x :> [`A | `C] Element.t)
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
[]
val f : [ `A ] Element.t -> [ `A | `C ] Element.t = <fun>

View File

@ -1,7 +1,7 @@
File "b_bad.ml", lines 13-14, characters 29-28:
13 | .............................function
14 | A.X s -> print_endline s
Error (warning 8): this pattern-matching is not exhaustive.
Error (warning 8 [partial-match]): this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Y
File "b_bad.ml", line 18, characters 11-14:

View File

@ -413,7 +413,7 @@ type i = I of int
Line 2, characters 0-34:
2 | external id : i -> i = "%identity";;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 61: This primitive declaration uses type i, whose representation
Warning 61 [unboxable-type-in-prim-decl]: This primitive declaration uses type i, whose representation
may be either boxed or unboxed. Without an annotation to indicate
which representation is intended, the boxed representation has been
selected by default. This default choice may change in future
@ -433,7 +433,7 @@ type j = J of int
Line 3, characters 0-34:
3 | external id : i -> j = "%identity";;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 61: This primitive declaration uses type i, whose representation
Warning 61 [unboxable-type-in-prim-decl]: This primitive declaration uses type i, whose representation
may be either boxed or unboxed. Without an annotation to indicate
which representation is intended, the boxed representation has been
selected by default. This default choice may change in future
@ -444,7 +444,7 @@ remains stable in the future.
Line 3, characters 0-34:
3 | external id : i -> j = "%identity";;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 61: This primitive declaration uses type j, whose representation
Warning 61 [unboxable-type-in-prim-decl]: This primitive declaration uses type j, whose representation
may be either boxed or unboxed. Without an annotation to indicate
which representation is intended, the boxed representation has been
selected by default. This default choice may change in future

View File

@ -27,7 +27,7 @@ let ambiguous_typical_example = function
Line 2, characters 4-29:
2 | | ((Val x, _) | (_, Val x)) when x < 0 -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable x may match different arguments. (See manual section 9.5)
val ambiguous_typical_example : expr * expr -> unit = <fun>
|}]
@ -94,7 +94,7 @@ let ambiguous__y = function
Line 2, characters 4-43:
2 | | (`B (x, _, Some y) | `B (x, Some y, _)) when y -> ignore x
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable y may match different arguments. (See manual section 9.5)
val ambiguous__y : [> `B of 'a * bool option * bool option ] -> unit = <fun>
|}]
@ -125,7 +125,7 @@ let ambiguous__x_y = function
Line 2, characters 4-43:
2 | | (`B (x, _, Some y) | `B (x, Some y, _)) when x < y -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable y may match different arguments. (See manual section 9.5)
val ambiguous__x_y : [> `B of 'a * 'a option * 'a option ] -> unit = <fun>
|}]
@ -138,7 +138,7 @@ let ambiguous__x_y_z = function
Line 2, characters 4-43:
2 | | (`B (x, z, Some y) | `B (x, Some y, z)) when x < y || Some x = z -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variables y,z may match different arguments. (See manual section 9.5)
val ambiguous__x_y_z : [> `B of 'a * 'a option * 'a option ] -> unit = <fun>
|}]
@ -169,7 +169,7 @@ let ambiguous__in_depth = function
Line 2, characters 4-40:
2 | | `A (`B (Some x, _) | `B (_, Some x)) when x -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable x may match different arguments. (See manual section 9.5)
val ambiguous__in_depth :
[> `A of [> `B of bool option * bool option ] ] -> unit = <fun>
@ -200,7 +200,7 @@ let ambiguous__first_orpat = function
Lines 2-3, characters 4-58:
2 | ....`A ((`B (Some x, _) | `B (_, Some x)),
3 | (`C (Some y, Some _, _) | `C (Some y, _, Some _))).................
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable x may match different arguments. (See manual section 9.5)
val ambiguous__first_orpat :
[> `A of
@ -218,7 +218,7 @@ let ambiguous__second_orpat = function
Lines 2-3, characters 4-42:
2 | ....`A ((`B (Some x, Some _, _) | `B (Some x, _, Some _)),
3 | (`C (Some y, _) | `C (_, Some y))).................
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable y may match different arguments. (See manual section 9.5)
val ambiguous__second_orpat :
[> `A of
@ -311,7 +311,7 @@ let ambiguous__amoi a = match a with
Lines 2-3, characters 2-17:
2 | ..X (Z x,Y (y,0))
3 | | X (Z y,Y (x,_))
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variables x,y may match different arguments. (See manual section 9.5)
val ambiguous__amoi : amoi -> int = <fun>
|}]
@ -331,7 +331,7 @@ let ambiguous__module_variable x b = match x with
Lines 2-3, characters 4-24:
2 | ....(module M:S),_,(1,_)
3 | | _,(module M:S),(_,1)...................
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable M may match different arguments. (See manual section 9.5)
val ambiguous__module_variable :
(module S) * (module S) * (int * int) -> bool -> int = <fun>
@ -346,7 +346,7 @@ let not_ambiguous__module_variable x b = match x with
Line 2, characters 12-13:
2 | | (module M:S),_,(1,_)
^
Warning 60: unused module M.
Warning 60 [unused-module]: unused module M.
val not_ambiguous__module_variable :
(module S) * (module S) * (int * int) -> bool -> int = <fun>
|}]
@ -367,18 +367,18 @@ let ambiguous_xy_but_not_ambiguous_z g = function
Line 2, characters 4-5:
2 | | A (x as z,(0 as y))|A (0 as y as z,x)|B (x,(y as z)) when g x (y+z) -> 1
^
Warning 41: A belongs to several types: t2 t
Warning 41 [ambiguous-name]: A belongs to several types: t2 t
The first one was selected. Please disambiguate if this is wrong.
Lines 1-3, characters 41-10:
1 | .........................................function
2 | | A (x as z,(0 as y))|A (0 as y as z,x)|B (x,(y as z)) when g x (y+z) -> 1
3 | | _ -> 2
Warning 4: this pattern-matching is fragile.
Warning 4 [fragile-match]: this pattern-matching is fragile.
It will remain exhaustive when constructors are added to type t2.
Line 2, characters 4-56:
2 | | A (x as z,(0 as y))|A (0 as y as z,x)|B (x,(y as z)) when g x (y+z) -> 1
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variables x,y may match different arguments. (See manual section 9.5)
val ambiguous_xy_but_not_ambiguous_z : (int -> int -> bool) -> t2 -> int =
<fun>
@ -386,28 +386,28 @@ val ambiguous_xy_but_not_ambiguous_z : (int -> int -> bool) -> t2 -> int =
Line 2, characters 4-5:
2 | | A (x as z,(0 as y))|A (0 as y as z,x)|B (x,(y as z)) when g x (y+z) -> 1
^
Warning 41: A belongs to several types: t2 t
Warning 41 [ambiguous-name]: A belongs to several types: t2 t
The first one was selected. Please disambiguate if this is wrong.
Line 2, characters 24-25:
2 | | A (x as z,(0 as y))|A (0 as y as z,x)|B (x,(y as z)) when g x (y+z) -> 1
^
Warning 41: A belongs to several types: t2 t
Warning 41 [ambiguous-name]: A belongs to several types: t2 t
The first one was selected. Please disambiguate if this is wrong.
Line 2, characters 42-43:
2 | | A (x as z,(0 as y))|A (0 as y as z,x)|B (x,(y as z)) when g x (y+z) -> 1
^
Warning 41: B belongs to several types: t2 t
Warning 41 [ambiguous-name]: B belongs to several types: t2 t
The first one was selected. Please disambiguate if this is wrong.
Lines 1-3, characters 41-10:
1 | .........................................function
2 | | A (x as z,(0 as y))|A (0 as y as z,x)|B (x,(y as z)) when g x (y+z) -> 1
3 | | _ -> 2
Warning 4: this pattern-matching is fragile.
Warning 4 [fragile-match]: this pattern-matching is fragile.
It will remain exhaustive when constructors are added to type t2.
Line 2, characters 4-56:
2 | | A (x as z,(0 as y))|A (0 as y as z,x)|B (x,(y as z)) when g x (y+z) -> 1
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variables x,y may match different arguments. (See manual section 9.5)
val ambiguous_xy_but_not_ambiguous_z : (int -> int -> bool) -> t2 -> int =
<fun>
@ -466,7 +466,7 @@ let guarded_ambiguity = function
Line 3, characters 4-29:
3 | | ((Val y, _) | (_, Val y)) when y < 0 -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable y may match different arguments. (See manual section 9.5)
val guarded_ambiguity : expr * expr -> unit = <fun>
|}]
@ -495,7 +495,7 @@ let cmp (pred : a -> bool) (x : a alg) (y : a alg) =
Line 4, characters 4-29:
4 | | ((Val x, _) | (_, Val x)) when pred x -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57: Ambiguous or-pattern variables under guard;
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable x may match different arguments. (See manual section 9.5)
val cmp : (a -> bool) -> a alg -> a alg -> unit = <fun>
|}]

View File

@ -19,7 +19,7 @@ let _ = Array.get [||];;
Line 1, characters 8-22:
1 | let _ = Array.get [||];;
^^^^^^^^^^^^^^
Warning 5: this function application is partial,
Warning 5 [ignored-partial-application]: this function application is partial,
maybe some arguments are missing.
- : int -> 'a = <fun>
|}]
@ -33,7 +33,7 @@ let () = ignore (Array.get [||]);;
Line 1, characters 16-32:
1 | let () = ignore (Array.get [||]);;
^^^^^^^^^^^^^^^^
Warning 5: this function application is partial,
Warning 5 [ignored-partial-application]: this function application is partial,
maybe some arguments are missing.
|}]
@ -48,7 +48,7 @@ let _ = if true then Array.get [||] else (fun _ -> 12);;
Line 1, characters 21-35:
1 | let _ = if true then Array.get [||] else (fun _ -> 12);;
^^^^^^^^^^^^^^
Warning 5: this function application is partial,
Warning 5 [ignored-partial-application]: this function application is partial,
maybe some arguments are missing.
- : int -> int = <fun>
|}]
@ -71,7 +71,7 @@ let f x = let _ = x.r 1 in ();;
Line 1, characters 18-23:
1 | let f x = let _ = x.r 1 in ();;
^^^^^
Warning 5: this function application is partial,
Warning 5 [ignored-partial-application]: this function application is partial,
maybe some arguments are missing.
val f : t -> unit = <fun>
|}]
@ -81,7 +81,7 @@ let _ = raise Exit 3;;
Line 1, characters 19-20:
1 | let _ = raise Exit 3;;
^
Warning 20: this argument will not be used by the function.
Warning 20 [ignored-extra-argument]: this argument will not be used by the function.
Exception: Stdlib.Exit.
|}]
@ -96,7 +96,7 @@ val g : int -> int = <fun>
Line 2, characters 10-15:
2 | let _ = g (f 1);;
^^^^^
Warning 5: this function application is partial,
Warning 5 [ignored-partial-application]: this function application is partial,
maybe some arguments are missing.
Line 2, characters 10-15:
2 | let _ = g (f 1);;

View File

@ -12,7 +12,7 @@ fun b -> if b then format_of_string "x" else "y"
Line 1, characters 45-48:
1 | fun b -> if b then format_of_string "x" else "y"
^^^
Warning 18: this coercion to format6 is not principal.
Warning 18 [not-principal]: this coercion to format6 is not principal.
- : bool -> ('a, 'b, 'c, 'd, 'd, 'a) format6 = <fun>
|}]
;;
@ -65,6 +65,6 @@ module Test1 : sig type t = private int val f : t -> int end
Line 3, characters 49-59:
3 | let f x = let y = if true then x else (x:t) in (y :> int)
^^^^^^^^^^
Warning 18: this ground coercion is not principal.
Warning 18 [not-principal]: this ground coercion is not principal.
module Test1 : sig type t = private int val f : t -> int end
|}]

View File

@ -11,7 +11,7 @@ Lines 1-3, characters 8-23:
1 | ........function
2 | None, None -> 1
3 | | Some _, Some _ -> 2..
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(None, Some _)
val f : 'a option * 'b option -> int = <fun>
@ -34,12 +34,12 @@ let f (x : int t) = match x with A -> 1 | _ -> 2;; (* warn *)
Line 1, characters 20-48:
1 | let f (x : int t) = match x with A -> 1 | _ -> 2;; (* warn *)
^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 4: this pattern-matching is fragile.
Warning 4 [fragile-match]: this pattern-matching is fragile.
It will remain exhaustive when constructors are added to type t.
Line 1, characters 42-43:
1 | let f (x : int t) = match x with A -> 1 | _ -> 2;; (* warn *)
^
Warning 56: this match case is unreachable.
Warning 56 [unreachable-case]: this match case is unreachable.
Consider replacing it with a refutation case '<pat> -> .'
val f : int t -> int = <fun>
|}]
@ -49,7 +49,7 @@ let f (x : unit t option) = match x with None -> 1 | _ -> 2 ;; (* warn? *)
Line 1, characters 53-54:
1 | let f (x : unit t option) = match x with None -> 1 | _ -> 2 ;; (* warn? *)
^
Warning 56: this match case is unreachable.
Warning 56 [unreachable-case]: this match case is unreachable.
Consider replacing it with a refutation case '<pat> -> .'
val f : unit t option -> int = <fun>
|}]
@ -59,7 +59,7 @@ let f (x : unit t option) = match x with None -> 1 | Some _ -> 2 ;; (* warn *)
Line 1, characters 53-59:
1 | let f (x : unit t option) = match x with None -> 1 | Some _ -> 2 ;; (* warn *)
^^^^^^
Warning 56: this match case is unreachable.
Warning 56 [unreachable-case]: this match case is unreachable.
Consider replacing it with a refutation case '<pat> -> .'
val f : unit t option -> int = <fun>
|}]
@ -74,7 +74,7 @@ let f (x : int t option) = match x with None -> 1;; (* warn *)
Line 1, characters 27-49:
1 | let f (x : int t option) = match x with None -> 1;; (* warn *)
^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Some A
val f : int t option -> int = <fun>
@ -94,7 +94,7 @@ let f : (int t box pair * bool) option -> unit = function None -> ();;
Line 1, characters 49-68:
1 | let f : (int t box pair * bool) option -> unit = function None -> ();;
^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Some ({left=Box A; right=Box A}, _)
val f : (int t box pair * bool) option -> unit = <fun>
@ -110,7 +110,7 @@ let f = function {left=Box 0; _ } -> ();;
Line 1, characters 8-39:
1 | let f = function {left=Box 0; _ } -> ();;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{left=Box 1; _ }
val f : int box pair -> unit = <fun>
@ -121,7 +121,7 @@ let f = function {left=Box 0;right=Box 1} -> ();;
Line 1, characters 8-47:
1 | let f = function {left=Box 0;right=Box 1} -> ();;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
{left=Box 0; right=Box 0}
val f : int box pair -> unit = <fun>
@ -178,7 +178,7 @@ let f : (A.a, A.b) cmp -> unit = function Any -> ()
Line 1, characters 33-51:
1 | let f : (A.a, A.b) cmp -> unit = function Any -> ()
^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Eq
val f : (A.a, A.b) cmp -> unit = <fun>
@ -231,7 +231,7 @@ let harder : (zero succ, zero succ, zero succ) plus option -> bool =
Line 2, characters 2-24:
2 | function None -> false
^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Some (PlusS _)
val harder : (zero succ, zero succ, zero succ) plus option -> bool = <fun>
@ -308,7 +308,7 @@ let f x y = match 1 with 1 when x = y -> 1;;
Line 1, characters 12-42:
1 | let f x y = match 1 with 1 when x = y -> 1;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
All clauses in this pattern-matching are guarded.
val f : 'a -> 'a -> int = <fun>
|}]
@ -319,7 +319,7 @@ let f = function {contents=_}, 0 -> 0;;
Line 1, characters 8-37:
1 | let f = function {contents=_}, 0 -> 0;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
(_, 1)
val f : 'a ref * int -> int = <fun>
@ -337,7 +337,7 @@ Lines 1-4, characters 8-28:
2 | | None -> ()
3 | | Some x when x > 0 -> ()
4 | | Some x when x <= 0 -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Some _
(However, some guarded clause may match this value.)
@ -373,7 +373,7 @@ Lines 20-22, characters 45-49:
20 | .............................................function
21 | | A, A, A, A -> ()
22 | | (A|B), (A|B), (A|B), A (*missing B here*) -> ()
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
((A|B), (A|B), (A|B), B)
module Single_row_optim :

View File

@ -8,7 +8,7 @@ let () = (let module L = List in raise Exit); () ;;
Line 1, characters 33-43:
1 | let () = (let module L = List in raise Exit); () ;;
^^^^^^^^^^
Warning 21: this statement never returns (or has an unsound type.)
Warning 21 [nonreturning-statement]: this statement never returns (or has an unsound type.)
Exception: Stdlib.Exit.
|}]
let () = (let exception E in raise Exit); ();;
@ -16,7 +16,7 @@ let () = (let exception E in raise Exit); ();;
Line 1, characters 29-39:
1 | let () = (let exception E in raise Exit); ();;
^^^^^^^^^^
Warning 21: this statement never returns (or has an unsound type.)
Warning 21 [nonreturning-statement]: this statement never returns (or has an unsound type.)
Exception: Stdlib.Exit.
|}]
let () = (raise Exit : _); ();;
@ -24,7 +24,7 @@ let () = (raise Exit : _); ();;
Line 1, characters 10-20:
1 | let () = (raise Exit : _); ();;
^^^^^^^^^^
Warning 21: this statement never returns (or has an unsound type.)
Warning 21 [nonreturning-statement]: this statement never returns (or has an unsound type.)
Exception: Stdlib.Exit.
|}]
let () = (let open Stdlib in raise Exit); ();;
@ -32,6 +32,6 @@ let () = (let open Stdlib in raise Exit); ();;
Line 1, characters 29-39:
1 | let () = (let open Stdlib in raise Exit); ();;
^^^^^^^^^^
Warning 21: this statement never returns (or has an unsound type.)
Warning 21 [nonreturning-statement]: this statement never returns (or has an unsound type.)
Exception: Stdlib.Exit.
|}]

View File

@ -10,11 +10,11 @@ end;;
Line 2, characters 20-26:
2 | module M = struct type t end (* unused type t *)
^^^^^^
Warning 34: unused type t.
Warning 34 [unused-type-declaration]: unused type t.
Line 3, characters 2-8:
3 | open M (* unused open *)
^^^^^^
Warning 33: unused open M.
Warning 33 [unused-open]: unused open M.
module T1 : sig end
|}]
@ -38,15 +38,15 @@ end;;
Line 4, characters 2-8:
4 | open M (* used by line below; shadow constructor A *)
^^^^^^
Warning 45: this open statement shadows the constructor A (which is later used)
Warning 45 [open-shadow-label-constructor]: this open statement shadows the constructor A (which is later used)
Line 2, characters 2-13:
2 | type t0 = A (* unused type and constructor *)
^^^^^^^^^^^
Warning 34: unused type t0.
Warning 34 [unused-type-declaration]: unused type t0.
Line 2, characters 12-13:
2 | type t0 = A (* unused type and constructor *)
^
Warning 37: unused constructor A.
Warning 37 [unused-constructor]: unused constructor A.
module T3 : sig end
|}]
@ -60,15 +60,15 @@ end;;
Line 3, characters 20-30:
3 | module M = struct type t = A end (* unused type and constructor *)
^^^^^^^^^^
Warning 34: unused type t.
Warning 34 [unused-type-declaration]: unused type t.
Line 3, characters 29-30:
3 | module M = struct type t = A end (* unused type and constructor *)
^
Warning 37: unused constructor A.
Warning 37 [unused-constructor]: unused constructor A.
Line 4, characters 2-8:
4 | open M (* unused open; no shadowing (A below refers to the one in t0) *)
^^^^^^
Warning 33: unused open M.
Warning 33 [unused-open]: unused open M.
module T4 : sig end
|}]
@ -82,15 +82,15 @@ end;;
Line 4, characters 2-8:
4 | open M (* shadow constructor A *)
^^^^^^
Warning 45: this open statement shadows the constructor A (which is later used)
Warning 45 [open-shadow-label-constructor]: this open statement shadows the constructor A (which is later used)
Line 2, characters 2-13:
2 | type t0 = A (* unused type and constructor *)
^^^^^^^^^^^
Warning 34: unused type t0.
Warning 34 [unused-type-declaration]: unused type t0.
Line 2, characters 12-13:
2 | type t0 = A (* unused type and constructor *)
^
Warning 37: unused constructor A.
Warning 37 [unused-constructor]: unused constructor A.
module T5 : sig end
|}]
@ -103,11 +103,11 @@ end;;
Line 2, characters 20-26:
2 | module M = struct type t end (* unused type t *)
^^^^^^
Warning 34: unused type t.
Warning 34 [unused-type-declaration]: unused type t.
Line 3, characters 2-9:
3 | open! M (* unused open *)
^^^^^^^
Warning 66: unused open! M.
Warning 66 [unused-open-bang]: unused open! M.
module T1_bis : sig end
|}]
@ -130,11 +130,11 @@ end;;
Line 2, characters 2-13:
2 | type t0 = A (* unused type and constructor *)
^^^^^^^^^^^
Warning 34: unused type t0.
Warning 34 [unused-type-declaration]: unused type t0.
Line 2, characters 12-13:
2 | type t0 = A (* unused type and constructor *)
^
Warning 37: unused constructor A.
Warning 37 [unused-constructor]: unused constructor A.
module T3_bis : sig end
|}]
@ -148,15 +148,15 @@ end;;
Line 3, characters 20-30:
3 | module M = struct type t = A end (* unused type and constructor *)
^^^^^^^^^^
Warning 34: unused type t.
Warning 34 [unused-type-declaration]: unused type t.
Line 3, characters 29-30:
3 | module M = struct type t = A end (* unused type and constructor *)
^
Warning 37: unused constructor A.
Warning 37 [unused-constructor]: unused constructor A.
Line 4, characters 2-9:
4 | open! M (* unused open; no shadowing (A below refers to the one in t0) *)
^^^^^^^
Warning 66: unused open! M.
Warning 66 [unused-open-bang]: unused open! M.
module T4_bis : sig end
|}]
@ -170,11 +170,11 @@ end;;
Line 2, characters 2-13:
2 | type t0 = A (* unused type and constructor *)
^^^^^^^^^^^
Warning 34: unused type t0.
Warning 34 [unused-type-declaration]: unused type t0.
Line 2, characters 12-13:
2 | type t0 = A (* unused type and constructor *)
^
Warning 37: unused constructor A.
Warning 37 [unused-constructor]: unused constructor A.
module T5_bis : sig end
|}]

View File

@ -17,7 +17,7 @@ let f : label choice -> bool = function Left -> true;; (* warn *)
Line 1, characters 31-52:
1 | let f : label choice -> bool = function Left -> true;; (* warn *)
^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Right
val f : CamlinternalOO.label choice -> bool = <fun>

View File

@ -27,7 +27,7 @@ A
Line 1, characters 0-1:
1 | A
^
Warning 41: A belongs to several types: a exn
Warning 41 [ambiguous-name]: A belongs to several types: a exn
The first one was selected. Please disambiguate if this is wrong.
- : a = A
|}]
@ -38,7 +38,7 @@ raise A
Line 1, characters 6-7:
1 | raise A
^
Warning 42: this use of A relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of A relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Exception: A.
|}]
@ -55,18 +55,18 @@ function Not_found -> 1 | A -> 2 | _ -> 3
Line 1, characters 26-27:
1 | function Not_found -> 1 | A -> 2 | _ -> 3
^
Warning 42: this use of A relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of A relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
- : exn -> int = <fun>
|}, Principal{|
Line 1, characters 26-27:
1 | function Not_found -> 1 | A -> 2 | _ -> 3
^
Warning 18: this type-based constructor disambiguation is not principal.
Warning 18 [not-principal]: this type-based constructor disambiguation is not principal.
Line 1, characters 26-27:
1 | function Not_found -> 1 | A -> 2 | _ -> 3
^
Warning 42: this use of A relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of A relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
- : exn -> int = <fun>
|}]
@ -77,12 +77,12 @@ try raise A with A -> 2
Line 1, characters 10-11:
1 | try raise A with A -> 2
^
Warning 42: this use of A relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of A relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 1, characters 17-18:
1 | try raise A with A -> 2
^
Warning 42: this use of A relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of A relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
- : int = 2
|}]

View File

@ -31,7 +31,7 @@ module type T =
Line 17, characters 5-35:
17 | match M.is_t () with None -> 0
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Some (Is Eq)
module Make : functor (M : T) -> sig val f : unit -> int end

View File

@ -16,7 +16,7 @@ end;;
Line 2, characters 10-11:
2 | let _f ~x (* x unused argument *) = function
^
Warning 27: unused variable x.
Warning 27 [unused-var-strict]: unused variable x.
module X1 : sig end
|}]
@ -29,7 +29,7 @@ end;;
Line 2, characters 6-7:
2 | let x = 42 (* unused value *)
^
Warning 32: unused value x.
Warning 32 [unused-value-declaration]: unused value x.
module X2 : sig end
|}]
@ -44,10 +44,10 @@ end;;
Line 2, characters 24-25:
2 | module O = struct let x = 42 (* unused *) end
^
Warning 32: unused value x.
Warning 32 [unused-value-declaration]: unused value x.
Line 3, characters 2-8:
3 | open O (* unused open *)
^^^^^^
Warning 33: unused open O.
Warning 33 [unused-open]: unused open O.
module X3 : sig end
|}]

View File

@ -5,6 +5,6 @@ Error: Syntax error
Line 2, characters 35-49:
2 | Foo: 'b * 'b -> foo constraint 'b = [> `Bla ];;
^^^^^^^^^^^^^^
Warning 62: Type constraints do not apply to GADT cases of variant types.
Warning 62 [constraint-on-gadt]: Type constraints do not apply to GADT cases of variant types.
type foo = Foo : 'b * 'b -> foo

View File

@ -14,6 +14,6 @@ let () = raise Exit; () ;; (* warn *)
Line 1, characters 9-19:
1 | let () = raise Exit; () ;; (* warn *)
^^^^^^^^^^
Warning 21: this statement never returns (or has an unsound type.)
Warning 21 [nonreturning-statement]: this statement never returns (or has an unsound type.)
Exception: Stdlib.Exit.
|}]

View File

@ -23,7 +23,7 @@ end = C;;
Line 2, characters 2-8:
2 | open A
^^^^^^
Warning 33: unused open A.
Warning 33 [unused-open]: unused open A.
module rec C : sig end
|}]
@ -39,12 +39,12 @@ end = D;;
Line 5, characters 10-14:
5 | let None = None
^^^^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
Some _
Line 4, characters 6-12:
4 | open A
^^^^^^
Warning 33: unused open A.
Warning 33 [unused-open]: unused open A.
module rec D : sig module M : sig module X : sig end end end
|}]

View File

@ -22,7 +22,7 @@ end
Line 5, characters 8-9:
5 | let x = 13
^
Warning 32: unused value x.
Warning 32 [unused-value-declaration]: unused value x.
module M : sig module F2 : U -> U end
|}]
@ -40,7 +40,7 @@ end
Line 5, characters 8-9:
5 | let x = 13
^
Warning 32: unused value x.
Warning 32 [unused-value-declaration]: unused value x.
module N : sig module F2 : U -> U end
|}]
@ -50,6 +50,6 @@ module F (X : sig type t type s end) = struct type t = X.t end
Line 1, characters 25-31:
1 | module F (X : sig type t type s end) = struct type t = X.t end
^^^^^^
Warning 34: unused type s.
Warning 34 [unused-type-declaration]: unused type s.
module F : functor (X : sig type t type s end) -> sig type t = X.t end
|}]

View File

@ -25,58 +25,58 @@ end;;
Line 3, characters 19-20:
3 | let f1 (r:t) = r.x (* ok *)
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 4, characters 29-30:
4 | let f2 r = ignore (r:t); r.x (* non principal *)
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 7, characters 18-19:
7 | match r with {x; y} -> y + y (* ok *)
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 7, characters 21-22:
7 | match r with {x; y} -> y + y (* ok *)
^
Warning 42: this use of y relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of y relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 7, characters 18-19:
7 | match r with {x; y} -> y + y (* ok *)
^
Warning 27: unused variable x.
Warning 27 [unused-var-strict]: unused variable x.
module OK :
sig val f1 : M1.t -> int val f2 : M1.t -> int val f3 : M1.t -> int end
|}, Principal{|
Line 3, characters 19-20:
3 | let f1 (r:t) = r.x (* ok *)
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 4, characters 29-30:
4 | let f2 r = ignore (r:t); r.x (* non principal *)
^
Warning 18: this type-based field disambiguation is not principal.
Warning 18 [not-principal]: this type-based field disambiguation is not principal.
Line 4, characters 29-30:
4 | let f2 r = ignore (r:t); r.x (* non principal *)
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 7, characters 18-19:
7 | match r with {x; y} -> y + y (* ok *)
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 7, characters 21-22:
7 | match r with {x; y} -> y + y (* ok *)
^
Warning 42: this use of y relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of y relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 7, characters 18-19:
7 | match r with {x; y} -> y + y (* ok *)
^
Warning 27: unused variable x.
Warning 27 [unused-var-strict]: unused variable x.
module OK :
sig val f1 : M1.t -> int val f2 : M1.t -> int val f3 : M1.t -> int end
|}]
@ -89,7 +89,7 @@ end;; (* fails *)
Line 3, characters 25-31:
3 | let f r = match r with {x; y} -> y + y
^^^^^^
Warning 41: these field labels belong to several types: M1.u M1.t
Warning 41 [ambiguous-name]: these field labels belong to several types: M1.u M1.t
The first one was selected. Please disambiguate if this is wrong.
Line 3, characters 35-36:
3 | let f r = match r with {x; y} -> y + y
@ -109,37 +109,37 @@ end;; (* fails for -principal *)
Line 6, characters 8-9:
6 | {x; y} -> y + y
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 6, characters 11-12:
6 | {x; y} -> y + y
^
Warning 42: this use of y relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of y relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 6, characters 8-9:
6 | {x; y} -> y + y
^
Warning 27: unused variable x.
Warning 27 [unused-var-strict]: unused variable x.
module F2 : sig val f : M1.t -> int end
|}, Principal{|
Line 6, characters 8-9:
6 | {x; y} -> y + y
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 6, characters 11-12:
6 | {x; y} -> y + y
^
Warning 42: this use of y relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of y relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 6, characters 7-13:
6 | {x; y} -> y + y
^^^^^^
Warning 18: this type-based record disambiguation is not principal.
Warning 18 [not-principal]: this type-based record disambiguation is not principal.
Line 6, characters 8-9:
6 | {x; y} -> y + y
^
Warning 27: unused variable x.
Warning 27 [unused-var-strict]: unused variable x.
module F2 : sig val f : M1.t -> int end
|}]
@ -156,7 +156,7 @@ let f (r:M.t) = r.M.x;; (* ok *)
Line 1, characters 18-21:
1 | let f (r:M.t) = r.M.x;; (* ok *)
^^^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
val f : M.t -> int = <fun>
|}]
@ -165,13 +165,13 @@ let f (r:M.t) = r.x;; (* warning *)
Line 1, characters 18-19:
1 | let f (r:M.t) = r.x;; (* warning *)
^
Warning 40: x was selected from type M.t.
Warning 40 [name-out-of-scope]: x was selected from type M.t.
It is not visible in the current scope, and will not
be selected if the type becomes unknown.
Line 1, characters 18-19:
1 | let f (r:M.t) = r.x;; (* warning *)
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
val f : M.t -> int = <fun>
|}]
@ -180,12 +180,12 @@ let f ({x}:M.t) = x;; (* warning *)
Line 1, characters 8-9:
1 | let f ({x}:M.t) = x;; (* warning *)
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 1, characters 7-10:
1 | let f ({x}:M.t) = x;; (* warning *)
^^^
Warning 40: this record of type M.t contains fields that are
Warning 40 [name-out-of-scope]: this record of type M.t contains fields that are
not visible in the current scope: x.
They will not be selected if the type becomes unknown.
val f : M.t -> int = <fun>
@ -212,12 +212,12 @@ end;;
Line 4, characters 20-21:
4 | let f (r:M.t) = r.x
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 3, characters 2-8:
3 | open N
^^^^^^
Warning 33: unused open N.
Warning 33 [unused-open]: unused open N.
module OK : sig val f : M.t -> int end
|}]
@ -262,12 +262,12 @@ end;; (* ok *)
Line 3, characters 9-10:
3 | let f {x;z} = x,z
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 3, characters 8-13:
3 | let f {x;z} = x,z
^^^^^
Warning 9: the following labels are not bound in this record pattern:
Warning 9 [missing-record-field-pattern]: the following labels are not bound in this record pattern:
y
Either bind these labels explicitly or add '; _' to the pattern.
module OK : sig val f : M.u -> bool * char end
@ -280,7 +280,7 @@ end;; (* fail for missing label *)
Line 3, characters 11-12:
3 | let r = {x=true;z='z'}
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 3, characters 10-24:
3 | let r = {x=true;z='z'}
@ -297,12 +297,12 @@ end;; (* ok *)
Line 4, characters 11-12:
4 | let r = {x=3; y=true}
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 4, characters 16-17:
4 | let r = {x=3; y=true}
^
Warning 42: this use of y relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of y relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
module OK :
sig
@ -363,12 +363,12 @@ let r = {MN.x = 3; NM.y = 4};; (* error: type would change with order *)
Line 1, characters 8-28:
1 | let r = {MN.x = 3; NM.y = 4};; (* error: type would change with order *)
^^^^^^^^^^^^^^^^^^^^
Warning 41: x belongs to several types: MN.bar MN.foo
Warning 41 [ambiguous-name]: x belongs to several types: MN.bar MN.foo
The first one was selected. Please disambiguate if this is wrong.
Line 1, characters 8-28:
1 | let r = {MN.x = 3; NM.y = 4};; (* error: type would change with order *)
^^^^^^^^^^^^^^^^^^^^
Warning 41: y belongs to several types: NM.foo NM.bar
Warning 41 [ambiguous-name]: y belongs to several types: NM.foo NM.bar
The first one was selected. Please disambiguate if this is wrong.
Line 1, characters 19-23:
1 | let r = {MN.x = 3; NM.y = 4};; (* error: type would change with order *)
@ -398,7 +398,7 @@ end;;
Line 3, characters 37-38:
3 | let f r = ignore (r: foo); {r with x = 2; z = 3}
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 3, characters 44-45:
3 | let f r = ignore (r: foo); {r with x = 2; z = 3}
@ -426,7 +426,7 @@ end;;
Line 3, characters 38-39:
3 | let f r = ignore (r: foo); { r with x = 3; a = 4 }
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 3, characters 45-46:
3 | let f r = ignore (r: foo); { r with x = 3; a = 4 }
@ -443,12 +443,12 @@ end;;
Line 3, characters 11-12:
3 | let r = {x=1; y=2}
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 3, characters 16-17:
3 | let r = {x=1; y=2}
^
Warning 42: this use of y relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of y relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 4, characters 18-19:
4 | let r: other = {x=1; y=2}
@ -505,7 +505,7 @@ class f (_ : 'a) (_ : 'a) = object end;;
Line 1, characters 12-13:
1 | class g = f A;; (* ok *)
^
Warning 42: this use of A relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of A relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
class g : f
class f : 'a -> 'a -> object end
@ -515,28 +515,28 @@ class g = f (A : t) A;; (* warn with -principal *)
Line 1, characters 13-14:
1 | class g = f (A : t) A;; (* warn with -principal *)
^
Warning 42: this use of A relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of A relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 1, characters 20-21:
1 | class g = f (A : t) A;; (* warn with -principal *)
^
Warning 42: this use of A relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of A relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
class g : f
|}, Principal{|
Line 1, characters 13-14:
1 | class g = f (A : t) A;; (* warn with -principal *)
^
Warning 42: this use of A relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of A relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 1, characters 20-21:
1 | class g = f (A : t) A;; (* warn with -principal *)
^
Warning 18: this type-based constructor disambiguation is not principal.
Warning 18 [not-principal]: this type-based constructor disambiguation is not principal.
Line 1, characters 20-21:
1 | class g = f (A : t) A;; (* warn with -principal *)
^
Warning 42: this use of A relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of A relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
class g : f
|}]
@ -556,12 +556,12 @@ end;;
Line 7, characters 15-16:
7 | let y : t = {x = 0}
^
Warning 42: this use of x relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of x relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 6, characters 2-8:
6 | open M (* this open is unused, it isn't reported as shadowing 'x' *)
^^^^^^
Warning 33: unused open M.
Warning 33 [unused-open]: unused open M.
module Shadow1 :
sig
type t = { x : int; }
@ -581,11 +581,11 @@ end;;
Line 6, characters 2-8:
6 | open M (* this open shadows label 'x' *)
^^^^^^
Warning 45: this open statement shadows the label x (which is later used)
Warning 45 [open-shadow-label-constructor]: this open statement shadows the label x (which is later used)
Line 7, characters 10-18:
7 | let y = {x = ""}
^^^^^^^^
Warning 41: these field labels belong to several types: M.s t
Warning 41 [ambiguous-name]: these field labels belong to several types: M.s t
The first one was selected. Please disambiguate if this is wrong.
module Shadow2 :
sig
@ -607,7 +607,7 @@ end;;
Line 5, characters 37-40:
5 | let f (u : u) = match u with `Key {loc} -> loc
^^^
Warning 42: this use of loc relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of loc relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
module P6235 :
sig
@ -632,7 +632,7 @@ end;;
Line 7, characters 11-14:
7 | |`Key {loc} -> loc
^^^
Warning 42: this use of loc relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of loc relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
module P6235' :
sig
@ -645,12 +645,12 @@ module P6235' :
Line 7, characters 11-14:
7 | |`Key {loc} -> loc
^^^
Warning 42: this use of loc relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of loc relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 7, characters 10-15:
7 | |`Key {loc} -> loc
^^^^^
Warning 18: this type-based record disambiguation is not principal.
Warning 18 [not-principal]: this type-based record disambiguation is not principal.
module P6235' :
sig
type t = { loc : string; }
@ -689,47 +689,47 @@ module M : sig type t = { x : int; y : char; } end
Line 2, characters 27-28:
2 | let f (x : M.t) = { x with y = 'a' }
^
Warning 42: this use of y relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of y relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 2, characters 18-36:
2 | let f (x : M.t) = { x with y = 'a' }
^^^^^^^^^^^^^^^^^^
Warning 40: this record of type M.t contains fields that are
Warning 40 [name-out-of-scope]: this record of type M.t contains fields that are
not visible in the current scope: y.
They will not be selected if the type becomes unknown.
val f : M.t -> M.t = <fun>
Line 3, characters 27-28:
3 | let g (x : M.t) = { x with y = 'a' } :: []
^
Warning 42: this use of y relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of y relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 3, characters 18-36:
3 | let g (x : M.t) = { x with y = 'a' } :: []
^^^^^^^^^^^^^^^^^^
Warning 40: this record of type M.t contains fields that are
Warning 40 [name-out-of-scope]: this record of type M.t contains fields that are
not visible in the current scope: y.
They will not be selected if the type becomes unknown.
val g : M.t -> M.t list = <fun>
Line 4, characters 27-28:
4 | let h (x : M.t) = { x with y = 'a' } :: { x with y = 'b' } :: [];;
^
Warning 42: this use of y relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of y relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 4, characters 18-36:
4 | let h (x : M.t) = { x with y = 'a' } :: { x with y = 'b' } :: [];;
^^^^^^^^^^^^^^^^^^
Warning 40: this record of type M.t contains fields that are
Warning 40 [name-out-of-scope]: this record of type M.t contains fields that are
not visible in the current scope: y.
They will not be selected if the type becomes unknown.
Line 4, characters 49-50:
4 | let h (x : M.t) = { x with y = 'a' } :: { x with y = 'b' } :: [];;
^
Warning 42: this use of y relies on type-directed disambiguation,
Warning 42 [disambiguated-name]: this use of y relies on type-directed disambiguation,
it will not compile with OCaml 4.00 or earlier.
Line 4, characters 40-58:
4 | let h (x : M.t) = { x with y = 'a' } :: { x with y = 'b' } :: [];;
^^^^^^^^^^^^^^^^^^
Warning 40: this record of type M.t contains fields that are
Warning 40 [name-out-of-scope]: this record of type M.t contains fields that are
not visible in the current scope: y.
They will not be selected if the type becomes unknown.
val h : M.t -> M.t list = <fun>

View File

@ -8,7 +8,7 @@ module Foo(Unused : sig end) = struct end;;
Line 1, characters 11-17:
1 | module Foo(Unused : sig end) = struct end;;
^^^^^^
Warning 60: unused module Unused.
Warning 60 [unused-module]: unused module Unused.
module Foo : functor (Unused : sig end) -> sig end
|}]
@ -17,7 +17,7 @@ module type S = functor (Unused : sig end) -> sig end;;
Line 1, characters 25-31:
1 | module type S = functor (Unused : sig end) -> sig end;;
^^^^^^
Warning 67: unused functor parameter Unused.
Warning 67 [unused-functor-parameter]: unused functor parameter Unused.
module type S = functor (Unused : sig end) -> sig end
|}]
@ -28,6 +28,6 @@ end;;
Line 2, characters 12-18:
2 | module M (Unused : sig end) : sig end
^^^^^^
Warning 67: unused functor parameter Unused.
Warning 67 [unused-functor-parameter]: unused functor parameter Unused.
module type S = sig module M : functor (Unused : sig end) -> sig end end
|}]

View File

@ -9,7 +9,7 @@ let rec f () = 3;;
Line 3, characters 8-9:
3 | let rec f () = 3;;
^
Warning 39: unused rec flag.
Warning 39 [unused-rec-flag]: unused rec flag.
val f : unit -> int = <fun>
|}];;
@ -23,7 +23,7 @@ let[@warning "+39"] rec h () = 3;;
Line 1, characters 24-25:
1 | let[@warning "+39"] rec h () = 3;;
^
Warning 39: unused rec flag.
Warning 39 [unused-rec-flag]: unused rec flag.
val h : unit -> int = <fun>
|}];;
@ -44,6 +44,6 @@ let[@warning "+39"] rec h () = 3;;
Line 1, characters 24-25:
1 | let[@warning "+39"] rec h () = 3;;
^
Warning 39: unused rec flag.
Warning 39 [unused-rec-flag]: unused rec flag.
val h : unit -> int = <fun>
|}];;

View File

@ -26,6 +26,6 @@ end;;
Line 14, characters 4-10:
14 | type t
^^^^^^
Warning 34: unused type t.
Warning 34 [unused-type-declaration]: unused type t.
module M : sig end
|}];;

View File

@ -12,7 +12,7 @@ end
Line 3, characters 2-19:
3 | type unused = int
^^^^^^^^^^^^^^^^^
Warning 34: unused type unused.
Warning 34 [unused-type-declaration]: unused type unused.
module Unused : sig end
|}]
@ -26,7 +26,7 @@ end
Line 4, characters 2-27:
4 | type nonrec unused = used
^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 34: unused type unused.
Warning 34 [unused-type-declaration]: unused type unused.
module Unused_nonrec : sig end
|}]
@ -39,11 +39,11 @@ end
Line 3, characters 2-27:
3 | type unused = A of unused
^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 34: unused type unused.
Warning 34 [unused-type-declaration]: unused type unused.
Line 3, characters 16-27:
3 | type unused = A of unused
^^^^^^^^^^^
Warning 37: unused constructor A.
Warning 37 [unused-constructor]: unused constructor A.
module Unused_rec : sig end
|}]
@ -69,7 +69,7 @@ end
Line 4, characters 11-12:
4 | type t = T
^
Warning 37: unused constructor T.
Warning 37 [unused-constructor]: unused constructor T.
module Unused_constructor : sig type t end
|}]
@ -86,7 +86,7 @@ end
Line 5, characters 11-12:
5 | type t = T
^
Warning 37: constructor T is never used to build values.
Warning 37 [unused-constructor]: constructor T is never used to build values.
(However, this constructor appears in patterns.)
module Unused_constructor_outside_patterns :
sig type t val nothing : t -> unit end
@ -102,7 +102,7 @@ end
Line 4, characters 11-12:
4 | type t = T
^
Warning 37: constructor T is never used to build values.
Warning 37 [unused-constructor]: constructor T is never used to build values.
Its type is exported as a private type.
module Unused_constructor_exported_private : sig type t = private T end
|}]
@ -130,7 +130,7 @@ end
Line 4, characters 19-20:
4 | type t = private T
^
Warning 37: unused constructor T.
Warning 37 [unused-constructor]: unused constructor T.
module Unused_private_constructor : sig type t end
|}]
@ -177,7 +177,7 @@ end
Line 3, characters 2-26:
3 | exception Nobody_uses_me
^^^^^^^^^^^^^^^^^^^^^^^^
Warning 38: unused exception Nobody_uses_me
Warning 38 [unused-extension]: unused exception Nobody_uses_me
module Unused_exception : sig end
|}]
@ -192,7 +192,7 @@ end
Line 5, characters 12-26:
5 | type t += Nobody_uses_me
^^^^^^^^^^^^^^
Warning 38: unused extension constructor Nobody_uses_me
Warning 38 [unused-extension]: unused extension constructor Nobody_uses_me
module Unused_extension_constructor : sig type t = .. end
|}]
@ -209,7 +209,7 @@ end
Line 4, characters 2-32:
4 | exception Nobody_constructs_me
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 38: exception Nobody_constructs_me is never used to build values.
Warning 38 [unused-extension]: exception Nobody_constructs_me is never used to build values.
(However, this constructor appears in patterns.)
module Unused_exception_outside_patterns : sig val falsity : exn -> bool end
|}]
@ -229,7 +229,7 @@ end
Line 6, characters 12-27:
6 | type t += Noone_builds_me
^^^^^^^^^^^^^^^
Warning 38: extension constructor Noone_builds_me is never used to build values.
Warning 38 [unused-extension]: extension constructor Noone_builds_me is never used to build values.
(However, this constructor appears in patterns.)
module Unused_extension_outside_patterns :
sig type t = .. val falsity : t -> bool end
@ -245,7 +245,7 @@ end
Line 4, characters 2-23:
4 | exception Private_exn
^^^^^^^^^^^^^^^^^^^^^
Warning 38: exception Private_exn is never used to build values.
Warning 38 [unused-extension]: exception Private_exn is never used to build values.
It is exported or rebound as a private extension.
module Unused_exception_exported_private :
sig type exn += private Private_exn end
@ -263,7 +263,7 @@ end
Line 6, characters 12-23:
6 | type t += Private_ext
^^^^^^^^^^^
Warning 38: extension constructor Private_ext is never used to build values.
Warning 38 [unused-extension]: extension constructor Private_ext is never used to build values.
It is exported or rebound as a private extension.
module Unused_extension_exported_private :
sig type t = .. type t += private Private_ext end
@ -294,7 +294,7 @@ end
Line 5, characters 20-31:
5 | type t += private Private_ext
^^^^^^^^^^^
Warning 38: unused extension constructor Private_ext
Warning 38 [unused-extension]: unused extension constructor Private_ext
module Unused_private_extension : sig type t end
|}]
@ -330,7 +330,7 @@ end;;
Line 3, characters 11-12:
3 | type t = A [@@warning "-34"]
^
Warning 37: unused constructor A.
Warning 37 [unused-constructor]: unused constructor A.
module Unused_type_disable_warning : sig end
|}]
@ -342,6 +342,6 @@ end;;
Line 3, characters 2-30:
3 | type t = A [@@warning "-37"]
^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 34: unused type t.
Warning 34 [unused-type-declaration]: unused type t.
module Unused_constructor_disable_warning : sig end
|}]

View File

@ -0,0 +1,84 @@
(* TEST
ocamllex_flags = "-q"
*)
{
}
let ws = [' ''\t']
let nl = '\n'
let constr = ['A'-'Z']['a'-'z''A'-'Z''0'-'9''_']*
let int = ['0'-'9']+
let mnemo = ['a'-'z']['a'-'z''-']*['a'-'z']
rule seek_let_number_function = parse
| ws* "let" ws+ "number" ws* "=" ws* "function" ws* '\n'
{ () }
| [^'\n']* '\n'
{ seek_let_number_function lexbuf }
and constructors = parse
| ws* '|' ws* (constr as c) (ws* '_')? ws* "->" ws* (int as n) [^'\n']* '\n'
{ (c, int_of_string n) :: constructors lexbuf }
| ws* ";;" ws* '\n'
{ [] }
and mnemonics = parse
| ws* (int as n) ws+ '[' (mnemo as s) ']' [^'\n']* '\n'
{ (s, int_of_string n) :: mnemonics lexbuf }
| [^'\n']* '\n'
{ mnemonics lexbuf }
| eof
{ [] }
{
let ocamlsrcdir = Sys.getenv "ocamlsrcdir"
let ocamlrun = Sys.getenv "ocamlrun"
let constructors =
let ic = open_in Filename.(concat ocamlsrcdir (concat "utils" "warnings.ml")) in
Fun.protect ~finally:(fun () -> close_in_noerr ic)
(fun () ->
let lexbuf = Lexing.from_channel ic in
seek_let_number_function lexbuf;
constructors lexbuf
)
let mnemonics =
let stdout = "warn-help.out" in
let n =
Sys.command
Filename.(quote_command ~stdout
ocamlrun [concat ocamlsrcdir "ocamlc"; "-warn-help"])
in
assert (n = 0);
let ic = open_in stdout in
Fun.protect ~finally:(fun () -> close_in_noerr ic)
(fun () ->
let lexbuf = Lexing.from_channel ic in
mnemonics lexbuf
)
let mnemonic_of_constructor s =
String.map (function '_' -> '-' | c -> Char.lowercase_ascii c) s
let () =
List.iter (fun (s, n) ->
let f (c, m) = mnemonic_of_constructor c = s && n = m in
if not (List.exists f constructors) then
Printf.printf "Could not find constructor corresponding to mnemonic %S (%d)\n%!" s n
) mnemonics
let _ =
List.fold_left (fun first (c, m) ->
if List.mem (mnemonic_of_constructor c, m) mnemonics then first
else begin
if first then print_endline "Constructors without associated mnemonic:";
print_endline c;
false
end
) true constructors
}

View File

@ -0,0 +1,2 @@
Constructors without associated mnemonic:
All_clauses_guarded

View File

@ -1,27 +1,27 @@
File "w01.ml", line 14, characters 12-14:
14 | let foo = ( *);;
^^
Warning 2: this is not the end of a comment.
Warning 2 [comment-not-end]: this is not the end of a comment.
File "w01.ml", line 20, characters 0-3:
20 | f 1; f 1;;
^^^
Warning 5: this function application is partial,
Warning 5 [ignored-partial-application]: this function application is partial,
maybe some arguments are missing.
File "w01.ml", line 30, characters 4-5:
30 | let 1 = 1;;
^
Warning 8: this pattern-matching is not exhaustive.
Warning 8 [partial-match]: this pattern-matching is not exhaustive.
Here is an example of a case that is not matched:
0
File "w01.ml", line 35, characters 0-1:
35 | 1; 1;;
^
Warning 10: this expression should have type unit.
Warning 10 [non-unit-statement]: this expression should have type unit.
File "w01.ml", line 42, characters 2-3:
42 | | 1 -> ()
^
Warning 11: this match case is unused.
Warning 11 [redundant-case]: this match case is unused.
File "w01.ml", line 19, characters 8-9:
19 | let f x y = x;;
^
Warning 27: unused variable y.
Warning 27 [unused-var-strict]: unused variable y.

View File

@ -5,4 +5,4 @@ Alert deprecated: A
File "w03.ml", line 17, characters 12-26:
17 | exception B [@@deprecated]
^^^^^^^^^^^^^^
Warning 53: the "deprecated" attribute cannot appear in this context
Warning 53 [misplaced-attribute]: the "deprecated" attribute cannot appear in this context

View File

@ -2,5 +2,5 @@ File "w04.ml", lines 21-23, characters 10-8:
21 | ..........match x with
22 | | A -> 0
23 | | _ -> 1
Warning 4: this pattern-matching is fragile.
Warning 4 [fragile-match]: this pattern-matching is fragile.
It will remain exhaustive when constructors are added to type t.

View File

@ -3,19 +3,19 @@ File "w04_failure.ml", lines 20-23, characters 2-17:
21 | | AB, _, A -> ()
22 | | _, XY, X -> ()
23 | | _, _, _ -> ()
Warning 4: this pattern-matching is fragile.
Warning 4 [fragile-match]: this pattern-matching is fragile.
It will remain exhaustive when constructors are added to type repr.
File "w04_failure.ml", lines 20-23, characters 2-17:
20 | ..match r1, r2, t with
21 | | AB, _, A -> ()
22 | | _, XY, X -> ()
23 | | _, _, _ -> ()
Warning 4: this pattern-matching is fragile.
Warning 4 [fragile-match]: this pattern-matching is fragile.
It will remain exhaustive when constructors are added to type ab.
File "w04_failure.ml", lines 20-23, characters 2-17:
20 | ..match r1, r2, t with
21 | | AB, _, A -> ()
22 | | _, XY, X -> ()
23 | | _, _, _ -> ()
Warning 4: this pattern-matching is fragile.
Warning 4 [fragile-match]: this pattern-matching is fragile.
It will remain exhaustive when constructors are added to type xy.

View File

@ -1,8 +1,8 @@
File "w06.ml", line 16, characters 9-12:
16 | let () = foo 2
^^^
Warning 6: label bar was omitted in the application of this function.
Warning 6 [labels-omitted]: label bar was omitted in the application of this function.
File "w06.ml", line 17, characters 9-12:
17 | let () = bar 4 2
^^^
Warning 6: labels foo, baz were omitted in the application of this function.
Warning 6 [labels-omitted]: labels foo, baz were omitted in the application of this function.

View File

@ -1,63 +1,63 @@
File "w32.mli", line 12, characters 10-11:
12 | module F (X : sig val x : int end) : sig end
^
Warning 67: unused functor parameter X.
Warning 67 [unused-functor-parameter]: unused functor parameter X.
File "w32.mli", line 14, characters 10-11:
14 | module G (X : sig val x : int end) : sig end
^
Warning 67: unused functor parameter X.
Warning 67 [unused-functor-parameter]: unused functor parameter X.
File "w32.mli", line 16, characters 10-11:
16 | module H (X : sig val x : int end) : sig val x : int end
^
Warning 67: unused functor parameter X.
Warning 67 [unused-functor-parameter]: unused functor parameter X.
File "w32.ml", line 40, characters 24-25:
40 | let[@warning "-32"] rec q x = x
^
Warning 39: unused rec flag.
Warning 39 [unused-rec-flag]: unused rec flag.
File "w32.ml", line 43, characters 24-25:
43 | let[@warning "-32"] rec s x = x
^
Warning 39: unused rec flag.
Warning 39 [unused-rec-flag]: unused rec flag.
File "w32.ml", line 20, characters 4-5:
20 | let h x = x
^
Warning 32: unused value h.
Warning 32 [unused-value-declaration]: unused value h.
File "w32.ml", line 26, characters 4-5:
26 | and j x = x
^
Warning 32: unused value j.
Warning 32 [unused-value-declaration]: unused value j.
File "w32.ml", line 28, characters 4-5:
28 | let k x = x
^
Warning 32: unused value k.
Warning 32 [unused-value-declaration]: unused value k.
File "w32.ml", line 41, characters 4-5:
41 | and r x = x
^
Warning 32: unused value r.
Warning 32 [unused-value-declaration]: unused value r.
File "w32.ml", line 44, characters 20-21:
44 | and[@warning "-39"] t x = x
^
Warning 32: unused value t.
Warning 32 [unused-value-declaration]: unused value t.
File "w32.ml", line 46, characters 24-25:
46 | let[@warning "-39"] rec u x = x
^
Warning 32: unused value u.
Warning 32 [unused-value-declaration]: unused value u.
File "w32.ml", line 47, characters 4-5:
47 | and v x = v x
^
Warning 32: unused value v.
Warning 32 [unused-value-declaration]: unused value v.
File "w32.ml", line 55, characters 22-23:
55 | let[@warning "+32"] g x = x
^
Warning 32: unused value g.
Warning 32 [unused-value-declaration]: unused value g.
File "w32.ml", line 56, characters 22-23:
56 | let[@warning "+32"] h x = x
^
Warning 32: unused value h.
Warning 32 [unused-value-declaration]: unused value h.
File "w32.ml", line 59, characters 22-23:
59 | and[@warning "+32"] k x = x
^
Warning 32: unused value k.
Warning 32 [unused-value-declaration]: unused value k.
File "w32.ml", lines 52-60, characters 0-3:
52 | module M = struct
53 | [@@@warning "-32"]
@ -68,16 +68,16 @@ File "w32.ml", lines 52-60, characters 0-3:
58 | let j x = x
59 | and[@warning "+32"] k x = x
60 | end
Warning 60: unused module M.
Warning 60 [unused-module]: unused module M.
File "w32.ml", line 63, characters 18-29:
63 | module F (X : sig val x : int end) = struct end
^^^^^^^^^^^
Warning 32: unused value x.
Warning 32 [unused-value-declaration]: unused value x.
File "w32.ml", line 63, characters 10-11:
63 | module F (X : sig val x : int end) = struct end
^
Warning 60: unused module X.
Warning 60 [unused-module]: unused module X.
File "w32.ml", line 65, characters 18-29:
65 | module G (X : sig val x : int end) = X
^^^^^^^^^^^
Warning 32: unused value x.
Warning 32 [unused-value-declaration]: unused value x.

View File

@ -1,8 +1,8 @@
File "w32b.ml", line 13, characters 18-24:
13 | module Q (M : sig type t end) = struct end
^^^^^^
Warning 34: unused type t.
Warning 34 [unused-type-declaration]: unused type t.
File "w32b.ml", line 13, characters 10-11:
13 | module Q (M : sig type t end) = struct end
^
Warning 60: unused module M.
Warning 60 [unused-module]: unused module M.

View File

@ -1,12 +1,12 @@
File "w33.ml", line 19, characters 6-11:
19 | let f M.(x) = x (* useless open *)
^^^^^
Warning 33: unused open M.
Warning 33 [unused-open]: unused open M.
File "w33.ml", line 26, characters 0-7:
26 | open! M (* useless open! *)
^^^^^^^
Warning 66: unused open! M.
Warning 66 [unused-open-bang]: unused open! M.
File "w33.ml", line 27, characters 0-6:
27 | open M (* useless open *)
^^^^^^
Warning 33: unused open M.
Warning 33 [unused-open]: unused open M.

View File

@ -1,13 +1,13 @@
File "w45.ml", line 24, characters 2-9:
24 | open T2 (* shadow X, which is later used; but not A, see #6762 *)
^^^^^^^
Warning 45: this open statement shadows the constructor X (which is later used)
Warning 45 [open-shadow-label-constructor]: this open statement shadows the constructor X (which is later used)
File "w45.ml", line 26, characters 14-15:
26 | let _ = (A, X) (* X belongs to several types *)
^
Warning 41: X belongs to several types: T2.s T1.s
Warning 41 [ambiguous-name]: X belongs to several types: T2.s T1.s
The first one was selected. Please disambiguate if this is wrong.
File "w45.ml", line 23, characters 2-9:
23 | open T1 (* unused open *)
^^^^^^^
Warning 33: unused open T1.
Warning 33 [unused-open]: unused open T1.

View File

@ -1,42 +1,42 @@
File "w47_inline.ml", line 30, characters 20-22:
30 | let[@local never] f2 x = x (* ok *) in
^^
Warning 26: unused variable f2.
Warning 26 [unused-var]: unused variable f2.
File "w47_inline.ml", line 31, characters 24-26:
31 | let[@local malformed] f3 x = x (* bad payload *) in
^^
Warning 26: unused variable f3.
Warning 26 [unused-var]: unused variable f3.
File "w47_inline.ml", line 15, characters 23-29:
15 | let d = (fun x -> x) [@inline malformed attribute] (* rejected *)
^^^^^^
Warning 47: illegal payload for attribute 'inline'.
Warning 47 [attribute-payload]: illegal payload for attribute 'inline'.
It must be either 'never', 'always', 'hint' or empty
File "w47_inline.ml", line 16, characters 23-29:
16 | let e = (fun x -> x) [@inline malformed_attribute] (* rejected *)
^^^^^^
Warning 47: illegal payload for attribute 'inline'.
Warning 47 [attribute-payload]: illegal payload for attribute 'inline'.
It must be either 'never', 'always', 'hint' or empty
File "w47_inline.ml", line 17, characters 23-29:
17 | let f = (fun x -> x) [@inline : malformed_attribute] (* rejected *)
^^^^^^
Warning 47: illegal payload for attribute 'inline'.
Warning 47 [attribute-payload]: illegal payload for attribute 'inline'.
It must be either 'never', 'always', 'hint' or empty
File "w47_inline.ml", line 18, characters 23-29:
18 | let g = (fun x -> x) [@inline ? malformed_attribute] (* rejected *)
^^^^^^
Warning 47: illegal payload for attribute 'inline'.
Warning 47 [attribute-payload]: illegal payload for attribute 'inline'.
It must be either 'never', 'always', 'hint' or empty
File "w47_inline.ml", line 23, characters 15-22:
23 | let k x = (a [@inlined malformed]) x (* rejected *)
^^^^^^^
Warning 47: illegal payload for attribute 'inlined'.
Warning 47 [attribute-payload]: illegal payload for attribute 'inlined'.
It must be either 'never', 'always', 'hint' or empty
File "w47_inline.ml", line 31, characters 7-12:
31 | let[@local malformed] f3 x = x (* bad payload *) in
^^^^^
Warning 47: illegal payload for attribute 'local'.
Warning 47 [attribute-payload]: illegal payload for attribute 'local'.
It must be either 'never', 'always', 'maybe' or empty
File "w47_inline.ml", line 32, characters 17-26:
32 | let[@local] f4 x = 2 * x (* not local *) in
^^^^^^^^^
Warning 55: Cannot inline: This function cannot be compiled into a static continuation
Warning 55 [inlining-impossible]: Cannot inline: This function cannot be compiled into a static continuation

View File

@ -1,8 +1,8 @@
File "w50.ml", line 13, characters 2-17:
13 | module L = List
^^^^^^^^^^^^^^^
Warning 60: unused module L.
Warning 60 [unused-module]: unused module L.
File "w50.ml", line 17, characters 2-16:
17 | module Y1 = X1
^^^^^^^^^^^^^^
Warning 60: unused module Y1.
Warning 60 [unused-module]: unused module Y1.

View File

@ -1,4 +1,4 @@
File "w51.ml", line 14, characters 13-37:
14 | | n -> n * (fact [@tailcall]) (n-1)
^^^^^^^^^^^^^^^^^^^^^^^^
Warning 51: expected tailcall
Warning 51 [tailcall-expected]: expected tailcall

View File

@ -1,4 +1,4 @@
File "w51_bis.ml", line 15, characters 12-48:
15 | try (foldl [@tailcall]) op (op x acc) xs
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 51: expected tailcall
Warning 51 [tailcall-expected]: expected tailcall

View File

@ -8,7 +8,7 @@ let () = try () with Invalid_argument "Any" -> ();;
Line 1, characters 38-43:
1 | let () = try () with Invalid_argument "Any" -> ();;
^^^^^
Warning 52: Code should not depend on the actual values of
Warning 52 [fragile-literal-pattern]: Code should not depend on the actual values of
this constructor's arguments. They are only for information
and may change in future versions. (See manual section 9.5)
|}];;
@ -18,7 +18,7 @@ let () = try () with Match_failure ("Any",_,_) -> ();;
Line 1, characters 35-46:
1 | let () = try () with Match_failure ("Any",_,_) -> ();;
^^^^^^^^^^^
Warning 52: Code should not depend on the actual values of
Warning 52 [fragile-literal-pattern]: Code should not depend on the actual values of
this constructor's arguments. They are only for information
and may change in future versions. (See manual section 9.5)
|}];;
@ -28,7 +28,7 @@ let () = try () with Match_failure (_,0,_) -> ();;
Line 1, characters 35-42:
1 | let () = try () with Match_failure (_,0,_) -> ();;
^^^^^^^
Warning 52: Code should not depend on the actual values of
Warning 52 [fragile-literal-pattern]: Code should not depend on the actual values of
this constructor's arguments. They are only for information
and may change in future versions. (See manual section 9.5)
|}];;
@ -53,7 +53,7 @@ let f = function
Line 2, characters 7-17:
2 | | Warn "anything" -> ()
^^^^^^^^^^
Warning 52: Code should not depend on the actual values of
Warning 52 [fragile-literal-pattern]: Code should not depend on the actual values of
this constructor's arguments. They are only for information
and may change in future versions. (See manual section 9.5)
val f : t -> unit = <fun>
@ -66,7 +66,7 @@ let g = function
Line 2, characters 8-10:
2 | | Warn' 0n -> ()
^^
Warning 52: Code should not depend on the actual values of
Warning 52 [fragile-literal-pattern]: Code should not depend on the actual values of
this constructor's arguments. They are only for information
and may change in future versions. (See manual section 9.5)
val g : t -> unit = <fun>
@ -93,7 +93,7 @@ let j = function
Line 2, characters 7-34:
2 | | Deep (_ :: _ :: ("deep",_) :: _) -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 52: Code should not depend on the actual values of
Warning 52 [fragile-literal-pattern]: Code should not depend on the actual values of
this constructor's arguments. They are only for information
and may change in future versions. (See manual section 9.5)
val j : t -> unit = <fun>

Some files were not shown because too many files have changed in this diff Show More