Skip to content

Commit

Permalink
Merge pull request #315 from alainfrisch/all_clause_guarded_warning
Browse files Browse the repository at this point in the history
"All clauses guarded" warning (25) now part of standard "non exhaustive" warning (8)
  • Loading branch information
alainfrisch committed Dec 9, 2015
2 parents d311a3b + 8602717 commit 360d3ca
Show file tree
Hide file tree
Showing 4 changed files with 19 additions and 6 deletions.
2 changes: 2 additions & 0 deletions Changes
Expand Up @@ -78,6 +78,8 @@ Compilers:
- PR#6845: -no-check-prims to tell ocamlc not to check primitives in runtime
* PR#6865: remove special case for parsing "let _ = expr" in structures
(Jérémie Dimino, Alain Frisch)
* PR#6438: Pattern guard disables exhaustiveness check
(Alain Frisch)
- PR#6939: Segfault with improper use of let-rec (Alain Frisch)
- PR#6943: native-code generator for POWER/PowerPC 64 bits, both in
big-endian (ppc64) and little-endian (ppc64le) configuration.
Expand Down
4 changes: 4 additions & 0 deletions testsuite/tests/typing-warnings/exhaustiveness.ml
Expand Up @@ -103,3 +103,7 @@ let f () = match None with _ -> .;; (* error *)
let g () = match None with _ -> () | exception _ -> .;; (* error *)
let h () = match None with _ -> . | exception _ -> .;; (* error *)
let f x = match x with _ -> () | None -> .;; (* do not warn *)

(* #7059, all clauses guarded *)

let f x y = match 1 with 1 when x = y -> 1;;
6 changes: 6 additions & 0 deletions testsuite/tests/typing-warnings/exhaustiveness.ml.reference
Expand Up @@ -113,4 +113,10 @@ Error: This match case could not be refuted.
Error: This match case could not be refuted.
Here is an example of a value that would reach it: _
# val f : 'a option -> unit = <fun>
# Characters 47-77:
let f x y = match 1 with 1 when x = y -> 1;;
^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
Warning 8: this pattern-matching is not exhaustive.
All clauses in this pattern-matching are guarded.
val f : 'a -> 'a -> int = <fun>
#
13 changes: 7 additions & 6 deletions utils/warnings.ml
Expand Up @@ -42,7 +42,7 @@ type t =
| Preprocessor of string (* 22 *)
| Useless_record_with (* 23 *)
| Bad_module_name of string (* 24 *)
| All_clauses_guarded (* 25 *)
| All_clauses_guarded (* 8, used to be 25 *)
| Unused_var of string (* 26 *)
| Unused_var_strict of string (* 27 *)
| Wildcard_arg_to_constant_constr (* 28 *)
Expand Down Expand Up @@ -107,7 +107,7 @@ let number = function
| Preprocessor _ -> 22
| Useless_record_with -> 23
| Bad_module_name _ -> 24
| All_clauses_guarded -> 25
| All_clauses_guarded -> 8 (* used to be 25 *)
| Unused_var _ -> 26
| Unused_var_strict _ -> 27
| Wildcard_arg_to_constant_constr -> 28
Expand Down Expand Up @@ -171,7 +171,7 @@ let letter = function
| 'u' -> [11; 12]
| 'v' -> [13]
| 'w' -> []
| 'x' -> [14; 15; 16; 17; 18; 19; 20; 21; 22; 23; 24; 25; 30]
| 'x' -> [14; 15; 16; 17; 18; 19; 20; 21; 22; 23; 24; 30]
| 'y' -> [26]
| 'z' -> [27]
| _ -> assert false
Expand Down Expand Up @@ -324,7 +324,8 @@ let message = function
| Bad_module_name (modname) ->
"bad source file name: \"" ^ modname ^ "\" is not a valid module name."
| All_clauses_guarded ->
"bad style, all clauses in this pattern-matching are guarded."
"this pattern-matching is not exhaustive.\n\
All clauses in this pattern-matching are guarded."
| Unused_var v | Unused_var_strict v -> "unused variable " ^ v ^ "."
| Wildcard_arg_to_constant_constr ->
"wildcard pattern given as argument to a constant constructor"
Expand Down Expand Up @@ -482,8 +483,8 @@ let descriptions =
23, "Useless record \"with\" clause.";
24, "Bad module name: the source file name is not a valid OCaml module \
name.";
25, "Pattern-matching with all clauses guarded. Exhaustiveness cannot be\n\
\ checked.";
(* 25, "Pattern-matching with all clauses guarded. Exhaustiveness cannot be\n\
\ checked."; (* Now part of warning 8 *) *)
26, "Suspicious unused variable: unused variable that is bound\n\
\ with \"let\" or \"as\", and doesn't start with an underscore (\"_\")\n\
\ character.";
Expand Down

0 comments on commit 360d3ca

Please sign in to comment.