Skip to content

Commit

Permalink
erl_lint: Warn on remote-calling non-exported functions
Browse files Browse the repository at this point in the history
Fixes #9092
  • Loading branch information
jhogberg committed Nov 20, 2024
1 parent cdd61f5 commit b9f7f88
Show file tree
Hide file tree
Showing 3 changed files with 59 additions and 6 deletions.
1 change: 1 addition & 0 deletions lib/eunit/src/eunit_test.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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").
Expand Down
23 changes: 20 additions & 3 deletions lib/stdlib/src/erl_lint.erl
Original file line number Diff line number Diff line change
Expand Up @@ -346,6 +346,8 @@ format_error_1({define_import,{F,A}}) ->
{~"defining imported function ~tw/~w", [F,A]};
format_error_1({unused_function,{F,A}}) ->
{~"function ~tw/~w is unused", [F,A]};
format_error_1({unexported_function, MFA}) ->
{~"function ~ts is not exported", [format_mfa(MFA)]};
format_error_1({call_to_redefined_bif,{F,A}}) ->
{~"""
ambiguous call of overridden auto-imported BIF ~w/~w --
Expand Down Expand Up @@ -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],
Expand Down Expand Up @@ -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_exported_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);
Expand All @@ -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_exported_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),
Expand Down Expand Up @@ -3023,6 +3031,15 @@ is_valid_call(Call) ->
_ -> true
end.

check_exported_function(Anno, M, F, A, #lint{module=M}=St) ->
case (is_warn_enabled(unexported_function, St) andalso
(not gb_sets:is_element({F, A}, exports(St)))) of
true -> add_warning(Anno, {unexported_function, {M, F, A}}, St);
false -> St
end;
check_exported_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.
Expand Down
41 changes: 38 additions & 3 deletions lib/stdlib/test/erl_lint_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -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.
Expand Down Expand Up @@ -2736,7 +2771,7 @@ otp_5644(Config) when is_list(Config) ->
i(X) ->
X.
">>,
[],
[nowarn_unexported_function],
[]}],
[] = run(Config, Ts),
ok.
Expand Down Expand Up @@ -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.
Expand Down

0 comments on commit b9f7f88

Please sign in to comment.