Skip to content

Commit

Permalink
Merge pull request #10140 from gasche/require-full-labels
Browse files Browse the repository at this point in the history
enable warning 6 [labels-omitted] by default
  • Loading branch information
gasche committed Apr 14, 2021
2 parents b926823 + a93d732 commit 75902a8
Show file tree
Hide file tree
Showing 9 changed files with 65 additions and 50 deletions.
9 changes: 9 additions & 0 deletions Changes
Expand Up @@ -204,6 +204,15 @@ Working version
the source code than the point explicitly shown in the error message.
(François Pottier, review by Gabriel Scherer and Frédéric Bour.)

* #10118, #10140: enable warning 6 [labels-omitted] by default.
The following now warns:
let f ~x y = ... in f 3 5
the callsite (f 3 5) has to be turned into (f ~x:3 5).
This prevents mistakes where two arguments of the same types are swapped.
(Note: Dune already enables this warning by default.)
(Gabriel Scherer, review by Xavier Leroy and Florian Angeletti,
report by ygrek)

- #10196, #10197: better error message on empty character literals ''.
(Gabriel Scherer, review by David Allsopp and Florian Angeletti
and Daniel Bünzli, report by Robin Björklin)
Expand Down
2 changes: 1 addition & 1 deletion man/ocamlc.m
Expand Up @@ -1025,7 +1025,7 @@ compilation in any way (even if it is fatal). If a warning is enabled,

.IP
The default setting is
.BR \-w\ +a\-4\-6\-7\-9\-27\-29\-30\-32..42\-44\-45\-48\-50\-60\-66..70 .
.BR \-w\ +a\-4\-7\-9\-27\-29\-30\-32..42\-44\-45\-48\-50\-60\-66..70 .
Note that warnings
.BR 5 \ and \ 10
are not always triggered, depending on the internals of the type checker.
Expand Down
35 changes: 35 additions & 0 deletions manual/src/cmds/comp.etex
Expand Up @@ -358,6 +358,41 @@ command line, and possibly the "-custom" option.

This section describes and explains in detail some warnings:

\subsection{ss:warn6}{Warning 6: Label omitted in function application}

OCaml supports "labels-omitted" full applications: if the function has
a known arity, all the arguments are unlabeled, and their number
matches the number of non-optional parameters, then labels are ignored
and non-optional parameters are matched in their definition
order. Optional arguments are defaulted.

\begin{verbatim}
let f ~x ~y = x + y
let test = f 2 3

> let test = f 2 3
> ^
> Warning 6 [labels-omitted]: labels x, y were omitted in the application of this function.
\end{verbatim}

This support for "labels-omitted" application was introduced when
labels were added to OCaml, to ease the progressive introduction of
labels in a codebase. However, it has the downside of weakening the
labeling discipline: if you use labels to prevent callers from
mistakenly reordering two parameters of the same type, labels-omitted
make this mistake possible again.

Warning 6 warns when labels-omitted applications are used, to
discourage their use. When labels were introduced, this warning was
not enabled by default, so users would use labels-omitted
applications, often without noticing.

Over time, it has become idiomatic to enable this warning to avoid
argument-order mistakes. The warning is now on by default, since OCaml
4.13. Labels-omitted applications are not recommended anymore, but
users wishing to preserve this transitory style can disable the
warning explicitly.

\subsection{ss:warn9}{Warning 9: missing fields in a record pattern}

When pattern matching on records, it can be useful to match only few
Expand Down
20 changes: 7 additions & 13 deletions manual/src/refman/expr.etex
Expand Up @@ -293,24 +293,18 @@ let fullname ?title first second =
let name = fullname "Jane" "Fisher";;
\end{caml_example}

As a special case, if the function has a known arity, all the
arguments are unlabeled, and their number matches the number of
non-optional parameters, then labels are ignored and non-optional
parameters are matched in their definition order. Optional arguments
are defaulted.

\begin{caml_example}{toplevel}
let f ~a ?b c =
match b with Some n -> a + n + c | None -> a + c

let r = f 2 3;;
\end{caml_example}

In all cases but exact match of order and labels, without optional
parameters, the function type should be known at the application
point. This can be ensured by adding a type constraint. Principality
of the derivation can be checked in the "-principal" mode.

As a special case, OCaml supports "labels-omitted" full applications:
if the function has a known arity, all the arguments are unlabeled,
and their number matches the number of non-optional parameters, then
labels are ignored and non-optional parameters are matched in their
definition order. Optional arguments are defaulted. This omission of
labels is discouraged and results in a warning, see \ref{ss:warn6}.

\subsubsection*{sss:expr-function-definition}{Function definition}

Two syntactic forms are provided to define functions. The first form
Expand Down
29 changes: 0 additions & 29 deletions manual/src/tutorials/lablexamples.etex
Expand Up @@ -69,35 +69,6 @@ let hline ~x:x1 ~x:x2 ~y = (x1, x2, y);;
hline ~x:3 ~y:2 ~x:5;;
\end{caml_example}

As an exception to the above parameter matching rules, if an
application is total (omitting all optional arguments), labels may be
omitted.
In practice, many applications are total, so that labels can often be
omitted.
\begin{caml_example}{toplevel}
f 3 2;;
ListLabels.map succ [1;2;3];;
\end{caml_example}
But beware that functions like "ListLabels.fold_left" whose result
type is a type variable will never be considered as totally applied.
\begin{caml_example}{toplevel}[error]
ListLabels.fold_left ( + ) 0 [1;2;3];;
\end{caml_example}

When a function is passed as an argument to a higher-order function,
labels must match in both types. Neither adding nor removing labels
are allowed.
\begin{caml_example}{toplevel}
let h g = g ~x:3 ~y:2;;
h f;;
h ( + ) [@@expect error];;
\end{caml_example}
Note that when you don't need an argument, you can still use a wildcard
pattern, but you must prefix it with the label.
\begin{caml_example}{toplevel}
h (fun ~x:_ ~y -> y+1);;
\end{caml_example}

\subsection{ss:optional-arguments}{Optional arguments}

An interesting feature of labeled arguments is that they can be made
Expand Down
3 changes: 2 additions & 1 deletion testsuite/tests/lib-either/test.ml
Expand Up @@ -39,7 +39,8 @@ List.map is_right [left 1; right true];;
- : (unit, int) Either.t list = [Left (); Right 3]
|}];;

[map succ not (Left 1); map succ not (Right true)];;
[map ~left:succ ~right:not (Left 1);
map ~left:succ ~right:not (Right true)];;
[%%expect {|
- : (int, bool) Either.t list = [Left 2; Right false]
|}];;
Expand Down
7 changes: 6 additions & 1 deletion testsuite/tests/misc/exotic.ml
Expand Up @@ -10,7 +10,11 @@
Note that those tests are here to record this behavior and not to enshrine it.
*)

[@@@warning "-10-18-8-5"];;
[@@@warning "-non-unit-statement"];;
[@@@warning "-not-principal"];;
[@@@warning "-partial-match"];;
[@@@warning "-ignored-partial-application"];;

type t = A | () and b = B : _ -> b;;
[%%expect{|
type t = A | ()
Expand All @@ -35,6 +39,7 @@ true
|}]
;;

[@@@warning "-labels-omitted"];;
Clflags.strict_sequence := false;;
let f () = let g ~y = (raise Not_found : 'a) in
if false then ((assert false : 'a); g ()) else g ()
Expand Down
8 changes: 4 additions & 4 deletions testsuite/tools/expect_test.ml
Expand Up @@ -139,19 +139,19 @@ let collect_formatters buf pps ~f =
let ppb = Format.formatter_of_buffer buf in
let out_functions = Format.pp_get_formatter_out_functions ppb () in

List.iter (fun pp -> Format.pp_print_flush pp ()) pps;
List.iter ~f:(fun pp -> Format.pp_print_flush pp ()) pps;
let save =
List.map (fun pp -> Format.pp_get_formatter_out_functions pp ()) pps
List.map ~f:(fun pp -> Format.pp_get_formatter_out_functions pp ()) pps
in
let restore () =
List.iter2
(fun pp out_functions ->
~f:(fun pp out_functions ->
Format.pp_print_flush pp ();
Format.pp_set_formatter_out_functions pp out_functions)
pps save
in
List.iter
(fun pp -> Format.pp_set_formatter_out_functions pp out_functions)
~f:(fun pp -> Format.pp_set_formatter_out_functions pp out_functions)
pps;
match f () with
| x -> restore (); x
Expand Down
2 changes: 1 addition & 1 deletion utils/warnings.ml
Expand Up @@ -662,7 +662,7 @@ let parse_options errflag s =
alerts

(* If you change these, don't forget to change them in man/ocamlc.m *)
let defaults_w = "+a-4-6-7-9-27-29-30-32..42-44-45-48-50-60-66..70";;
let defaults_w = "+a-4-7-9-27-29-30-32..42-44-45-48-50-60-66..70";;
let defaults_warn_error = "-a+31";;

let () = ignore @@ parse_options false defaults_w;;
Expand Down

0 comments on commit 75902a8

Please sign in to comment.