Skip to content

Commit

Permalink
Clarify warning 57 message
Browse files Browse the repository at this point in the history
  • Loading branch information
wikku committed Feb 16, 2022
1 parent 3fa2cfc commit d2eb400
Show file tree
Hide file tree
Showing 3 changed files with 55 additions and 19 deletions.
3 changes: 3 additions & 0 deletions Changes
Original file line number Diff line number Diff line change
Expand Up @@ -257,6 +257,9 @@ OCaml 4.14.0
spurious `as 'a`s in types.
(Antal Spector-Zabusky, review by Florian Angeletti)

- #10794: Clarify warning 57 (Ambiguous or-pattern variables under guard)
(Wiktor Kuchta, review by Gabriel Scherer)

### Internal/compiler-libs changes:

- #1599: add unset directive to ocamltest to clear environment variables before
Expand Down
52 changes: 39 additions & 13 deletions testsuite/tests/typing-warnings/ambiguous_guarded_disjunction.ml
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,9 @@ Line 2, characters 4-29:
2 | | ((Val x, _) | (_, Val x)) when x < 0 -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable x may match different arguments. (See manual section 11.5)
variable x appears in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val ambiguous_typical_example : expr * expr -> unit = <fun>
|}]

Expand Down Expand Up @@ -95,7 +97,9 @@ Line 2, characters 4-43:
2 | | (`B (x, _, Some y) | `B (x, Some y, _)) when y -> ignore x
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable y may match different arguments. (See manual section 11.5)
variable y appears in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val ambiguous__y : [> `B of 'a * bool option * bool option ] -> unit = <fun>
|}]

Expand Down Expand Up @@ -126,7 +130,9 @@ Line 2, characters 4-43:
2 | | (`B (x, _, Some y) | `B (x, Some y, _)) when x < y -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable y may match different arguments. (See manual section 11.5)
variable y appears in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val ambiguous__x_y : [> `B of 'a * 'a option * 'a option ] -> unit = <fun>
|}]

Expand All @@ -139,7 +145,9 @@ 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-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variables y,z may match different arguments. (See manual section 11.5)
variables y, z appear in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val ambiguous__x_y_z : [> `B of 'a * 'a option * 'a option ] -> unit = <fun>
|}]

Expand Down Expand Up @@ -170,7 +178,9 @@ Line 2, characters 4-40:
2 | | `A (`B (Some x, _) | `B (_, Some x)) when x -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable x may match different arguments. (See manual section 11.5)
variable x appears in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val ambiguous__in_depth :
[> `A of [> `B of bool option * bool option ] ] -> unit = <fun>
|}]
Expand Down Expand Up @@ -201,7 +211,9 @@ 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-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable x may match different arguments. (See manual section 11.5)
variable x appears in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val ambiguous__first_orpat :
[> `A of
[> `B of 'a option * 'a option ] *
Expand All @@ -219,7 +231,9 @@ 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-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable y may match different arguments. (See manual section 11.5)
variable y appears in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val ambiguous__second_orpat :
[> `A of
[> `B of 'a option * 'b option * 'c option ] *
Expand Down Expand Up @@ -312,7 +326,9 @@ Lines 2-3, characters 2-17:
2 | ..X (Z x,Y (y,0))
3 | | X (Z y,Y (x,_))
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variables x,y may match different arguments. (See manual section 11.5)
variables x, y appear in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val ambiguous__amoi : amoi -> int = <fun>
|}]

Expand All @@ -332,7 +348,9 @@ Lines 2-3, characters 4-24:
2 | ....(module M:S),_,(1,_)
3 | | _,(module M:S),(_,1)...................
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable M may match different arguments. (See manual section 11.5)
variable M appears in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val ambiguous__module_variable :
(module S) * (module S) * (int * int) -> bool -> int = <fun>
|}]
Expand Down Expand Up @@ -379,7 +397,9 @@ 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-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variables x,y may match different arguments. (See manual section 11.5)
variables x, y appear in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val ambiguous_xy_but_not_ambiguous_z : (int -> int -> bool) -> t2 -> int =
<fun>
|}, Principal{|
Expand Down Expand Up @@ -408,7 +428,9 @@ 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-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variables x,y may match different arguments. (See manual section 11.5)
variables x, y appear in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val ambiguous_xy_but_not_ambiguous_z : (int -> int -> bool) -> t2 -> int =
<fun>
|}]
Expand Down Expand Up @@ -467,7 +489,9 @@ Line 3, characters 4-29:
3 | | ((Val y, _) | (_, Val y)) when y < 0 -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable y may match different arguments. (See manual section 11.5)
variable y appears in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val guarded_ambiguity : expr * expr -> unit = <fun>
|}]

Expand Down Expand Up @@ -496,7 +520,9 @@ Line 4, characters 4-29:
4 | | ((Val x, _) | (_, Val x)) when pred x -> ()
^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 57 [ambiguous-var-in-pattern-guard]: Ambiguous or-pattern variables under guard;
variable x may match different arguments. (See manual section 11.5)
variable x appears in different places in different or-pattern alternatives.
Only the first match will be used to evaluate the guard expression.
(See manual section 11.5)
val cmp : (a -> bool) -> a alg -> a alg -> unit = <fun>
|}]

Expand Down
19 changes: 13 additions & 6 deletions utils/warnings.ml
Original file line number Diff line number Diff line change
Expand Up @@ -966,17 +966,24 @@ let message = function
| Inlining_impossible reason ->
Printf.sprintf "Cannot inline: %s" reason
| Ambiguous_var_in_pattern_guard vars ->
let msg =
let vars = List.sort String.compare vars in
let vars = List.sort String.compare vars in
let vars_explanation =
let in_different_places =
"in different places in different or-pattern alternatives"
in
match vars with
| [] -> assert false
| [x] -> "variable " ^ x
| [x] -> "variable " ^ x ^ " appears " ^ in_different_places
| _::_ ->
"variables " ^ String.concat "," vars in
let vars = String.concat ", " vars in
"variables " ^ vars ^ " appear " ^ in_different_places
in
Printf.sprintf
"Ambiguous or-pattern variables under guard;\n\
%s may match different arguments. %t"
msg ref_manual_explanation
%s.\n\
Only the first match will be used to evaluate the guard expression.\n\
%t"
vars_explanation ref_manual_explanation
| No_cmx_file name ->
Printf.sprintf
"no cmx file was found in path for module %s, \
Expand Down

0 comments on commit d2eb400

Please sign in to comment.