File 4321-erl_parse-Provide-friendlier-head-mismatch-errors.patch of Package erlang

From d74e9c575075d49a749a30079b96be8d453dca55 Mon Sep 17 00:00:00 2001
From: Johannes Christ <jc@jchri.st>
Date: Thu, 8 Jun 2023 00:34:39 +0200
Subject: [PATCH] erl_parse: Provide friendlier "head mismatch" errors

Given the following module:

    %% mismatch.erl
    -module(mismatch).
    -compile([export_all, nowarn_export_all]).

    test_it(ok) -> ok;

    verify_it(true) -> ok;
    verify_it(false) -> {error, was_false}.
    verify_it(false, Reason) -> {error, Reason}.

On master, running `erlc mismatch.erl`  currently reports:

    mismatch.erl:6:1: head mismatch
    %    6| verify_it(true) -> ok;
    %     | ^

The previous clause that the parser is comparing to may not be obvious:
The current compiler warning points to `verify_it/1`, whose two clauses
are terminated properly. When more code is inbetween these two functions
(think documentation, specs, comments) the time needed to find the
mismatched clause can be a lot higher. I also believe that this will
make the error easier to understand for people new to Erlang.

With this commit, the compiler will output the following:

    mismatch.erl:6:1: head mismatch: previous function test_it/1 is distinct from verify_it/1. Is the semicolon in test_it/1 unwanted?
    %    6| verify_it(true) -> ok;
    %     | ^

For functions that are defined with the same name but distinct arities,
a separate error message is used, since the possibility of missed or
superfluous arguments also arises here. The following module illustrates
it:

    %% mismatch2.erl
    -module(mismatch2).
    -compile([export_all, nowarn_export_all]).

    verify_it(false) -> {error, was_false};
    verify_it(false, Reason) -> {error, Reason}.

The following error message is provided in this case:

    mismatch2.erl:6:1: head mismatch: function verify_it with arities 1 and 2 is regarded as two distinct functions. Is the number of arguments incorrect or is the semicolon in verify_it/1 unwanted?
    %    6| verify_it(false, Reason) -> {error, Reason}.
    %     | ^

For tools matching on the output of the compiler warnings, this is a
breaking change. I have so far only found Erlang LS which matches on
this [1]. Adding support for the extended information should be trivial.

[1]: https://github.com/erlang-ls/erlang_ls/blob/e315f9801d60e1ccbbfd444f32a33d00b0f6795d/apps/els_lsp/src/els_compiler_diagnostics.erl#L614
---
 lib/compiler/test/error_SUITE.erl             | 20 +++++++++++---
 .../head_mismatch_same_function_name.erl      | 26 +++++++++++++++++++
 lib/stdlib/src/erl_parse.yrl                  | 17 ++++++++++--
 3 files changed, 58 insertions(+), 5 deletions(-)
 create mode 100644 lib/compiler/test/error_SUITE_data/head_mismatch_same_function_name.erl

diff --git a/lib/compiler/test/error_SUITE.erl b/lib/compiler/test/error_SUITE.erl
index f82fde9e8b..3250ebb3d6 100644
--- a/lib/compiler/test/error_SUITE.erl
+++ b/lib/compiler/test/error_SUITE.erl
@@ -22,8 +22,8 @@
 
 -export([all/0, suite/0,groups/0,init_per_suite/1, end_per_suite/1, 
 	 init_per_group/2,end_per_group/2,
-	 head_mismatch_line/1,warnings_as_errors/1, bif_clashes/1,
-	 transforms/1,maps_warnings/1,bad_utf8/1,bad_decls/1]).
+	 head_mismatch_line/1, head_mismatch_same_function_name/1, warnings_as_errors/1,
+	 bif_clashes/1, transforms/1,maps_warnings/1,bad_utf8/1,bad_decls/1]).
 
 %% Used by transforms/1 test case.
 -export([parse_transform/2]).
@@ -35,7 +35,8 @@ all() ->
 
 groups() -> 
     [{p,test_lib:parallel(),
-      [head_mismatch_line,warnings_as_errors,bif_clashes,
+      [head_mismatch_line,head_mismatch_same_function_name,
+       warnings_as_errors,bif_clashes,
        transforms,maps_warnings,bad_utf8,bad_decls]}].
 
 init_per_suite(Config) ->
@@ -177,6 +178,19 @@ bif_clashes(Config) when is_list(Config) ->
 head_mismatch_line(Config) when is_list(Config) ->
     [E|_] = get_compilation_errors(Config, "head_mismatch_line"),
     {{26,1}, Mod, Reason} = E,
+    ("head mismatch: previous function foo/1 is distinct from bar/1. "
+     "Is the semicolon in foo/1 unwanted?") = lists:flatten(Reason),
+    Mod:format_error(Reason),
+    ok.
+
+%% Tests that a head mismatch with the same function name reports a different error from above.
+%% https://github.com/erlang/otp/pull/7383#issuecomment-1586564294
+head_mismatch_same_function_name(Config) when is_list(Config) ->
+    [E|_] = get_compilation_errors(Config, "head_mismatch_same_function_name"),
+    {{25,1}, Mod, Reason} = E,
+    ("head mismatch: function foo with arities 1 and 2 is regarded as "
+     "two distinct functions. Is the number of arguments incorrect "
+     "or is the semicolon in foo/1 unwanted?") = lists:flatten(Reason),
     Mod:format_error(Reason),
     ok.
 
diff --git a/lib/compiler/test/error_SUITE_data/head_mismatch_same_function_name.erl b/lib/compiler/test/error_SUITE_data/head_mismatch_same_function_name.erl
new file mode 100644
index 0000000000..2e02ca42c9
--- /dev/null
+++ b/lib/compiler/test/error_SUITE_data/head_mismatch_same_function_name.erl
@@ -0,0 +1,26 @@
+%%
+%% %CopyrightBegin%
+%% 
+%% Copyright Ericsson AB 1998-2016. All Rights Reserved.
+%% 
+%% Licensed under the Apache License, Version 2.0 (the "License");
+%% you may not use this file except in compliance with the License.
+%% You may obtain a copy of the License at
+%%
+%%     http://www.apache.org/licenses/LICENSE-2.0
+%%
+%% Unless required by applicable law or agreed to in writing, software
+%% distributed under the License is distributed on an "AS IS" BASIS,
+%% WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
+%% See the License for the specific language governing permissions and
+%% limitations under the License.
+%% 
+%% %CopyrightEnd%
+-module(head_mismatch_same_function_name).
+
+-export([foo/1, foo/2]).
+
+foo({A, B}) ->
+    A + B;
+foo(Other, State) ->
+    {Other, State}.
diff --git a/lib/stdlib/src/erl_parse.yrl b/lib/stdlib/src/erl_parse.yrl
index bef858cdc5..a1e41958a4 100644
--- a/lib/stdlib/src/erl_parse.yrl
+++ b/lib/stdlib/src/erl_parse.yrl
@@ -1499,8 +1499,21 @@ check_clauses(Cs, Name, Arity) ->
     [case C of
          {clause,A,N,As,G,B} when N =:= Name, length(As) =:= Arity ->
              {clause,A,As,G,B};
-         {clause,A,_N,_As,_G,_B} ->
-             ret_err(A, "head mismatch")
+         {clause,A,N,As,_G,_B} when N =:= Name ->
+             Detail = io_lib:format(
+                 "head mismatch: function ~s with arities ~w and ~w is "
+                 "regarded as two distinct functions. Is the number of "
+                 "arguments incorrect or is the semicolon in ~s/~w unwanted?",
+                 [Name, Arity, length(As), Name, Arity]
+             ),
+             ret_err(A, Detail);
+         {clause,A,N,As,_G,_B} ->
+             Detail = io_lib:format(
+                 "head mismatch: previous function ~s/~w is distinct from ~s/~w. "
+                 "Is the semicolon in ~s/~w unwanted?",
+                 [Name, Arity, N, length(As), Name, Arity]
+             ),
+             ret_err(A, Detail)
      end || C <- Cs].
 
 build_try(A,Es,Scs,{Ccs,As}) ->
-- 
2.35.3

openSUSE Build Service is sponsored by