Consistent name for Warning 52: Ambiguous or-pattern variables under guard
parent
62f0f5095c
commit
8de9e081d4
|
@ -835,7 +835,7 @@ match int_of_string count_str with
|
|||
end
|
||||
\end{verbatim}
|
||||
|
||||
\item[Warning 57: ambiguous variables in or-patterns]
|
||||
\item[Warning 57: Ambiguous or-pattern variables under guard]
|
||||
The semantics of or-patterns in OCaml is specified with
|
||||
a left-to-right bias: a value \var{v} matches the pattern \var{p} "|" \var{q}
|
||||
if it matches \var{p} or \var{q}, but if it matches both,
|
||||
|
|
|
@ -18,7 +18,8 @@ then just above there should be *no* warning text.
|
|||
# Characters 46-71:
|
||||
| ((Val x, _) | (_, Val x)) when x < 0 -> ()
|
||||
^^^^^^^^^^^^^^^^^^^^^^^^^
|
||||
Warning 57: Ambiguous guarded pattern, variable x may match different or-pattern arguments (see manual section 8.5)
|
||||
Warning 57: Ambiguous or-pattern variables under guard;
|
||||
variable x may match different arguments. (See manual section 8.5)
|
||||
val ambiguous_typical_example : expr * expr -> unit = <fun>
|
||||
# Note that an Assert_failure is expected just below.
|
||||
# Exception: Assert_failure ("//toplevel//", 23, 6).
|
||||
|
@ -33,19 +34,22 @@ val ambiguous_typical_example : expr * expr -> unit = <fun>
|
|||
# Characters 33-72:
|
||||
| (`B (x, _, Some y) | `B (x, Some y, _)) when y -> ignore x
|
||||
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
|
||||
Warning 57: Ambiguous guarded pattern, variable y may match different or-pattern arguments (see manual section 8.5)
|
||||
Warning 57: Ambiguous or-pattern variables under guard;
|
||||
variable y may match different arguments. (See manual section 8.5)
|
||||
val ambiguous__y : [> `B of 'a * bool option * bool option ] -> unit = <fun>
|
||||
# * * * * * * * * val not_ambiguous__rhs_not_protected :
|
||||
[> `B of 'a * bool option * bool option ] -> unit = <fun>
|
||||
# Characters 35-74:
|
||||
| (`B (x, _, Some y) | `B (x, Some y, _)) when x < y -> ()
|
||||
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
|
||||
Warning 57: Ambiguous guarded pattern, variable y may match different or-pattern arguments (see manual section 8.5)
|
||||
Warning 57: Ambiguous or-pattern variables under guard;
|
||||
variable y may match different arguments. (See manual section 8.5)
|
||||
val ambiguous__x_y : [> `B of 'a * 'a option * 'a option ] -> unit = <fun>
|
||||
# Characters 37-76:
|
||||
| (`B (x, z, Some y) | `B (x, Some y, z)) when x < y || Some x = z -> ()
|
||||
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
|
||||
Warning 57: Ambiguous guarded pattern, variables y,z may match different or-pattern arguments (see manual section 8.5)
|
||||
Warning 57: Ambiguous or-pattern variables under guard;
|
||||
variables y,z may match different arguments. (See manual section 8.5)
|
||||
val ambiguous__x_y_z : [> `B of 'a * 'a option * 'a option ] -> unit = <fun>
|
||||
# val not_ambiguous__disjoint_in_depth :
|
||||
[> `A of [> `B of bool | `C of bool ] ] -> unit = <fun>
|
||||
|
@ -54,7 +58,8 @@ val ambiguous__x_y_z : [> `B of 'a * 'a option * 'a option ] -> unit = <fun>
|
|||
# Characters 40-76:
|
||||
| `A (`B (Some x, _) | `B (_, Some x)) when x -> ()
|
||||
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
|
||||
Warning 57: Ambiguous guarded pattern, variable x may match different or-pattern arguments (see manual section 8.5)
|
||||
Warning 57: Ambiguous or-pattern variables under guard;
|
||||
variable x may match different arguments. (See manual section 8.5)
|
||||
val ambiguous__in_depth :
|
||||
[> `A of [> `B of bool option * bool option ] ] -> unit = <fun>
|
||||
# val not_ambiguous__several_orpats :
|
||||
|
@ -66,7 +71,8 @@ val ambiguous__in_depth :
|
|||
# Characters 43-140:
|
||||
....`A ((`B (Some x, _) | `B (_, Some x)),
|
||||
(`C (Some y, Some _, _) | `C (Some y, _, Some _))).................
|
||||
Warning 57: Ambiguous guarded pattern, variable x may match different or-pattern arguments (see manual section 8.5)
|
||||
Warning 57: Ambiguous or-pattern variables under guard;
|
||||
variable x may match different arguments. (See manual section 8.5)
|
||||
val ambiguous__first_orpat :
|
||||
[> `A of
|
||||
[> `B of 'a option * 'a option ] *
|
||||
|
@ -75,7 +81,8 @@ val ambiguous__first_orpat :
|
|||
# Characters 44-141:
|
||||
....`A ((`B (Some x, Some _, _) | `B (Some x, _, Some _)),
|
||||
(`C (Some y, _) | `C (_, Some y))).................
|
||||
Warning 57: Ambiguous guarded pattern, variable y may match different or-pattern arguments (see manual section 8.5)
|
||||
Warning 57: Ambiguous or-pattern variables under guard;
|
||||
variable y may match different arguments. (See manual section 8.5)
|
||||
val ambiguous__second_orpat :
|
||||
[> `A of
|
||||
[> `B of 'a option * 'b option * 'c option ] *
|
||||
|
@ -97,13 +104,15 @@ val ambiguous__second_orpat :
|
|||
# Characters 40-73:
|
||||
..X (Z x,Y (y,0))
|
||||
| X (Z y,Y (x,_))
|
||||
Warning 57: Ambiguous guarded pattern, variables x,y may match different or-pattern arguments (see manual section 8.5)
|
||||
Warning 57: Ambiguous or-pattern variables under guard;
|
||||
variables x,y may match different arguments. (See manual section 8.5)
|
||||
val ambiguous__amoi : amoi -> int = <fun>
|
||||
# module type S = sig val b : bool end
|
||||
# Characters 56-101:
|
||||
....(module M:S),_,(1,_)
|
||||
| _,(module M:S),(_,1)...................
|
||||
Warning 57: Ambiguous guarded pattern, variable M may match different or-pattern arguments (see manual section 8.5)
|
||||
Warning 57: Ambiguous or-pattern variables under guard;
|
||||
variable M may match different arguments. (See manual section 8.5)
|
||||
val ambiguous__module_variable :
|
||||
(module S) * (module S) * (int * int) -> bool -> int = <fun>
|
||||
# val not_ambiguous__module_variable :
|
||||
|
@ -123,7 +132,8 @@ It will remain exhaustive when constructors are added to type t.
|
|||
Characters 55-107:
|
||||
| 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 guarded pattern, variables x,y may match different or-pattern arguments (see manual section 8.5)
|
||||
Warning 57: Ambiguous or-pattern variables under guard;
|
||||
variables x,y may match different arguments. (See manual section 8.5)
|
||||
val ambiguous_xy_but_not_ambiguous_z : (int -> int -> bool) -> t -> int =
|
||||
<fun>
|
||||
#
|
||||
|
|
|
@ -455,8 +455,8 @@ let message = function
|
|||
| _::_ ->
|
||||
"variables " ^ String.concat "," vars in
|
||||
Printf.sprintf
|
||||
"Ambiguous guarded pattern, %s may match different or-pattern \
|
||||
arguments (see manual section 8.5)"
|
||||
"Ambiguous or-pattern variables under guard;\n\
|
||||
%s may match different arguments. (See manual section 8.5)"
|
||||
msg
|
||||
| No_cmx_file name ->
|
||||
Printf.sprintf
|
||||
|
@ -562,7 +562,7 @@ let descriptions =
|
|||
54, "Attribute used more than once on an expression";
|
||||
55, "Inlining impossible";
|
||||
56, "Unreachable case in a pattern-matching (based on type information).";
|
||||
57, "Ambiguous binding by pattern.";
|
||||
57, "Ambiguous or-pattern variables under guard";
|
||||
58, "Missing cmx file";
|
||||
59, "Assignment to non-mutable value";
|
||||
]
|
||||
|
|
Loading…
Reference in New Issue