File 8181-erl_lint-Warn-on-remote-calling-non-exported-functio.patch of Package erlang

From d87a951037b8b3c5630a05e2eeafea62a3d657c9 Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Wed, 20 Nov 2024 16:41:07 +0100
Subject: [PATCH] erl_lint: Warn on remote-calling non-exported functions

Fixes #9092
---
 lib/eunit/src/eunit_test.erl       |  1 +
 lib/stdlib/src/erl_lint.erl        | 29 ++++++++++++++++++---
 lib/stdlib/test/erl_lint_SUITE.erl | 41 +++++++++++++++++++++++++++---
 3 files changed, 65 insertions(+), 6 deletions(-)

diff --git a/lib/eunit/src/eunit_test.erl b/lib/eunit/src/eunit_test.erl
index ccb12ddd0e..7bccb9f394 100644
--- a/lib/eunit/src/eunit_test.erl
+++ b/lib/eunit/src/eunit_test.erl
@@ -29,6 +29,7 @@
 
 -export([run_testfun/1, mf_wrapper/2, enter_context/4, multi_setup/1]).
 
+-compile(nowarn_unexported_function).
 
 -include("eunit.hrl").
 -include("eunit_internal.hrl").
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index e05cf24e60..8a15221d65 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -274,6 +274,8 @@ format_error({define_import,{F,A}}) ->
     io_lib:format("defining imported function ~tw/~w", [F,A]);
 format_error({unused_function,{F,A}}) ->
     io_lib:format("function ~tw/~w is unused", [F,A]);
+format_error({unexported_function, MFA}) ->
+    io_lib:format("function ~ts is not exported", [format_mfa(MFA)]);
 format_error({call_to_redefined_bif,{F,A}}) ->
     io_lib:format("ambiguous call of overridden auto-imported BIF ~w/~w~n"
 		  " - use erlang:~w/~w or \"-compile({no_auto_import,[~w/~w]}).\" "
@@ -852,6 +854,9 @@ start(File, Opts) ->
          {ill_defined_optional_callbacks,
           bool_option(warn_ill_defined_optional_callbacks,
                       nowarn_ill_defined_optional_callbacks,
+                      true, Opts)},
+         {unexported_function,
+          bool_option(warn_unexported_function, nowarn_unexported_function,
                       true, Opts)}
 	],
     Enabled1 = [Category || {Category,true} <- Enabled0],
@@ -2772,8 +2777,10 @@ expr({'fun',Anno,Body}, Vt, St) ->
                 true -> {[],St};
                 false -> {[],call_function(Anno, F, A, St)}
             end;
-	{function,M,F,A} ->
-	    expr_list([M,F,A], Vt, St)
+        {function, {atom, _, M}, {atom, _, F}, {integer, _, A}} ->
+            {[], check_unexported_function(Anno, M, F, A, St)};
+        {function,M,F,A} ->
+            expr_list([M,F,A], Vt, St)
     end;
 expr({named_fun,_,'_',Cs}, Vt, St) ->
     fun_clauses(Cs, Vt, St);
@@ -2796,7 +2803,8 @@ expr({call,Anno,{remote,_Ar,{atom,_Am,M},{atom,Af,F}},As}, Vt, St0) ->
     St1 = keyword_warning(Af, F, St0),
     St2 = check_remote_function(Anno, M, F, As, St1),
     St3 = check_module_name(M, Anno, St2),
-    expr_list(As, Vt, St3);
+    St4 = check_unexported_function(Anno, M, F, length(As), St3),
+    expr_list(As, Vt, St4);
 expr({call,Anno,{remote,_Ar,M,F},As}, Vt, St0) ->
     St1 = keyword_warning(Anno, M, St0),
     St2 = keyword_warning(Anno, F, St1),
@@ -3023,6 +3031,21 @@ is_valid_call(Call) ->
         _ -> true
     end.
 
+%% Raises a warning if we're remote-calling an unexported function (or
+%% referencing it with `fun M:F/A`), as this is likely to be unintentional.
+check_unexported_function(Anno, M, F, A,
+                          #lint{module=M,
+                                compile=Opts,
+                                exports=Es} = St) ->
+    case (is_warn_enabled(unexported_function, St)
+          andalso (not lists:member(export_all, Opts))
+          andalso (not gb_sets:is_element({F, A}, Es))) of
+        true -> add_warning(Anno, {unexported_function, {M, F, A}}, St);
+        false -> St
+    end;
+check_unexported_function(_Anno, _M, _F, _A, St) ->
+    St.
+
 %% record_def(Anno, RecordName, [RecField], State) -> State.
 %%  Add a record definition if it does not already exist. Normalise
 %%  so that all fields have explicit initial value.
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 10bd35c566..c8305d4668 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -1181,7 +1181,42 @@ unused_function(Config) when is_list(Config) ->
                 32*X.
            ">>,
 	   {[]},		     %Tuple indicates no 'export_all'.
-	   []}],
+	   []},
+
+          %% Raises a warning that flurb/1 is unused, and that we should
+          %% probably export it because it's referenced in t/0 and u/1.
+          {func4,
+           <<"-export([t/0, u/1]).
+
+              t() ->
+                 fun ?MODULE:flurb/1.
+              u(X) ->
+                 ?MODULE:flurb(X).
+
+              flurb(X) ->
+                32*X.
+           ">>,
+           {[]}, %% Tuple indicates no 'export_all'.
+           {warnings,[{{4,18},erl_lint,{unexported_function,{lint_test,flurb,1}}},
+             {{6,19},erl_lint,{unexported_function,{lint_test,flurb,1}}},
+             {{8,15},erl_lint,{unused_function,{flurb,1}}}]}},
+
+          %% Turn off warnings for unexported functions using a -compile()
+          %% directive.
+          {func5,
+           <<"-export([t/0, u/1]).
+              -compile(nowarn_unexported_function).
+
+              t() ->
+                 fun ?MODULE:flurb/1.
+              u(X) ->
+                 ?MODULE:flurb(X).
+
+              flurb(X) ->
+                32*X.
+           ">>,
+           {[]}, %% Tuple indicates no 'export_all'.
+           {warnings,[{{9,15},erl_lint,{unused_function,{flurb,1}}}]}}],
 
     [] = run(Config, Ts),
     ok.
@@ -2736,7 +2771,7 @@ otp_5644(Config) when is_list(Config) ->
               i(X) ->
                   X.
             ">>,
-           [],
+           [nowarn_unexported_function],
            []}],
     [] = run(Config, Ts),
     ok.
@@ -3185,7 +3220,7 @@ bif_clash(Config) when is_list(Config) ->
               size({N,_}) ->
                 N.
              ">>,
-           [],
+           [nowarn_unexported_function],
 	   {errors,[{{2,19},erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}},
 
 	  %% Verify that warnings cannot be turned off in the old way.
-- 
2.43.0

openSUSE Build Service is sponsored by