Skip to content

Commit

Permalink
compiler: Improve error messages for using a function with wrong arity
Browse files Browse the repository at this point in the history
When a function is used with wrong arity, the compiler will try to
suggest all defined functions with the same name but different arities.
For example, given the following module:

    -module(typos).
    -export([t/0]).
    bar(A) -> A.
    bar(A,A,A) -> A.
    bar(A,A,A,A) -> A.
    t() -> bar(0, 0).

The compiler will emit the following message:

    typo.erl:6:12: function bar/2 undefined, did you mean bar/1,3,4?
    %   6|     t() -> bar(0, 0).
    %    |            ^

Error types that are extended by this change: `bad_inline`,
`undefined_nif`, `bad_nowarn_unused_function`, `bad_nowarn_bif_clash`,
`undefined_function`.

Using a function with wrong arity has higher precedence than having
a typo in the function name. If the compiler can find a defined function
with the same name but a different arity, it will not suggest a defined
function with a close-enough name, regardless of arity.
  • Loading branch information
lucioleKi committed Nov 22, 2024
1 parent cdd61f5 commit 4b67a69
Show file tree
Hide file tree
Showing 2 changed files with 92 additions and 64 deletions.
72 changes: 40 additions & 32 deletions lib/stdlib/src/erl_lint.erl
Original file line number Diff line number Diff line change
Expand Up @@ -283,12 +283,12 @@ format_error_1({redefine_import,{{F,A},M}}) ->
{~"function ~tw/~w already imported from ~w", [F,A,M]};
format_error_1({bad_inline,{F,A}}) ->
{~"inlined function ~tw/~w undefined", [F,A]};
format_error_1({bad_inline,{F,A},GuessF}) ->
{~"inlined function ~tw/~w undefined, did you mean ~ts/~w?", [F,A,GuessF,A]};
format_error_1({bad_inline,{F,A},GuessFA}) ->
{~"inlined function ~tw/~w undefined, did you mean ~s?", [F,A,format_fa(GuessFA)]};
format_error_1({undefined_nif,{F,A}}) ->
{~"nif ~tw/~w undefined", [F,A]};
format_error_1({undefined_nif,{F,A},GuessF}) ->
{~"nif ~tw/~w undefined, did you mean ~ts/~w?", [F,A,GuessF,A]};
format_error_1({undefined_nif,{F,A},GuessFA}) ->
{~"nif ~tw/~w undefined, did you mean ~s?", [F,A,format_fa(GuessFA)]};
format_error_1(no_load_nif) ->
{~"nifs defined, but no call to erlang:load_nif/2", []};
format_error_1({invalid_deprecated,D}) ->
Expand All @@ -305,10 +305,12 @@ format_error_1({bad_removed,{F,A}}) ->
{~"removed function ~tw/~w is still exported", [F,A]};
format_error_1({bad_nowarn_unused_function,{F,A}}) ->
{~"function ~tw/~w undefined", [F,A]};
format_error_1({bad_nowarn_unused_function,{F,A},GuessF}) ->
{~"function ~tw/~w undefined, did you mean ~ts/~w?", [F,A,GuessF,A]};
format_error_1({bad_nowarn_unused_function,{F,A},GuessFA}) ->
{~"function ~tw/~w undefined, did you mean ~s?", [F,A,format_fa(GuessFA)]};
format_error_1({bad_nowarn_bif_clash,{F,A}}) ->
{~"function ~tw/~w undefined", [F,A]};
format_error_1({bad_nowarn_bif_clash,{F,A},GuessFA}) ->
{~"function ~tw/~w undefined, did you mean ~s?", [F,A,format_fa(GuessFA)]};
format_error_1(disallowed_nowarn_bif_clash) ->
~"""
compile directive nowarn_bif_clash is no longer allowed --
Expand Down Expand Up @@ -338,8 +340,8 @@ format_error_1({unused_import,{{F,A},M}}) ->
{~"import ~w:~tw/~w is unused", [M,F,A]};
format_error_1({undefined_function,{F,A}}) ->
{~"function ~tw/~w undefined", [F,A]};
format_error_1({undefined_function,{F,A},GuessF}) ->
{~"function ~tw/~w undefined, did you mean ~ts/~w?", [F,A,GuessF,A]};
format_error_1({undefined_function,{F,A},GuessFA}) ->
{~"function ~tw/~w undefined, did you mean ~s?", [F,A,format_fa(GuessFA)]};
format_error_1({redefine_function,{F,A}}) ->
{~"function ~tw/~w already defined", [F,A]};
format_error_1({define_import,{F,A}}) ->
Expand Down Expand Up @@ -616,6 +618,10 @@ format_mfa({M, F, [_|_]=As}) ->
format_mfa({M, F, A}) when is_integer(A) ->
format_mf(M, F, integer_to_list(A)).

format_fa({F, [_|_]=As}) ->
","++ArityString = lists:append([[$,|integer_to_list(A)] || A <- As]),
atom_to_list(F) ++ "/" ++ ArityString.

format_mf(M, F, ArityString) when is_atom(M), is_atom(F) ->
atom_to_list(M) ++ ":" ++ atom_to_list(F) ++ "/" ++ ArityString.

Expand Down Expand Up @@ -1604,14 +1610,7 @@ check_undefined_functions(#lint{called=Called0,defined=Def0}=St0) ->
Def = sofs:from_external(gb_sets:to_list(Def0), [func]),
Undef = sofs:to_external(sofs:drestriction(Called, Def)),
FAList = sofs:to_external(Def),
foldl(fun ({NA,Anno}, St) ->
{Name, Arity} = NA,
PossibleFs = [atom_to_list(F) || {F, A} <- FAList, A =:= Arity],
case most_possible_string(Name, PossibleFs) of
[] -> add_error(Anno, {undefined_function,NA}, St);
GuessF -> add_error(Anno, {undefined_function,NA,GuessF}, St)
end
end, St0, Undef).
func_location_error(undefined_function, Undef, St0, FAList).

most_possible_string(Name, PossibleNames) ->
case PossibleNames of
Expand All @@ -1626,7 +1625,7 @@ most_possible_string(Name, PossibleNames) ->
F <- PossibleNames],
{MaxSim, GuessName} = lists:last(lists:sort(Similarities)),
case MaxSim > SufficientlySimilar of
true -> GuessName;
true -> list_to_atom(GuessName);
false -> []
end
end.
Expand Down Expand Up @@ -1686,15 +1685,26 @@ nowarn_function(Tag, Opts) ->
func_location_warning(Type, Fs, St) ->
foldl(fun ({F,Anno}, St0) -> add_warning(Anno, {Type,F}, St0) end, St, Fs).

func_location_error(Type, Fs, St, FAList) ->
foldl(fun ({F,Anno}, St0) ->
{Name, Arity} = F,
PossibleFs = [atom_to_list(Func) || {Func, A} <- FAList, A =:= Arity],
case most_possible_string(Name, PossibleFs) of
[] -> add_error(Anno, {Type,F}, St0);
GuessF -> add_error(Anno, {Type,F,GuessF}, St0)
end
end, St, Fs).
func_location_error(Type, [{F,Anno}|Fs], St0, FAList) ->
{Name, Arity} = F,
PossibleAs = lists:sort([A || {FName, A} <:- FAList, FName =:= Name]),
case PossibleAs of
[] ->
PossibleFs = [atom_to_list(Func) ||
{Func, A} <:- FAList, A =:= Arity],
St1 = case most_possible_string(Name, PossibleFs) of
[] ->
add_error(Anno, {Type,F}, St0);
GuessF ->
add_error(Anno, {Type,F,{GuessF,[Arity]}}, St0)
end,
func_location_error(Type, Fs, St1, FAList);
_ ->
St1 = add_error(Anno, {Type,F,{Name,PossibleAs}}, St0),
func_location_error(Type, Fs, St1, FAList)
end;
func_location_error(_, [], St, _) ->
St.

check_untyped_records(Forms, St0) ->
case is_warn_enabled(untyped_record, St0) of
Expand Down Expand Up @@ -3832,12 +3842,10 @@ check_dialyzer_attribute(Forms, St0) ->
case lists:member(FA, DefFunctions) of
true -> St;
false ->
{Name, Arity} = FA,
PossibleFs = [atom_to_list(F) || {F, A} <- DefFunctions, A =:= Arity],
case most_possible_string(Name, PossibleFs) of
[] -> add_error(Anno, {undefined_function,FA}, St);
GuessF -> add_error(Anno, {undefined_function,FA,GuessF}, St)
end
func_location_error(undefined_function,
[{FA,Anno}],
St,
DefFunctions)
end;
false ->
add_error(Anno, {bad_dialyzer_option,Option}, St)
Expand Down
84 changes: 52 additions & 32 deletions lib/stdlib/test/erl_lint_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -1493,15 +1493,15 @@ unsafe_vars_try(Config) when is_list(Config) ->
{errors,[{{5,41},erl_lint,{unsafe_var,'R',{'try',{3,19}}}},
{{7,24},erl_lint,{unsafe_var,'Rc',{'try',{3,19}}}},
{{13,38},erl_lint,{unsafe_var,'R',{'try',{10,19}}}},
{{13,40},erl_lint,{unbound_var,'RR',"R"}},
{{13,43},erl_lint,{unbound_var,'Ro',"R"}},
{{13,40},erl_lint,{unbound_var,'RR','R'}},
{{13,43},erl_lint,{unbound_var,'Ro','R'}},
{{15,24},erl_lint,{unsafe_var,'R',{'try',{10,19}}}},
{{15,26},erl_lint,{unsafe_var,'RR',{'try',{10,19}}}},
{{15,29},erl_lint,{unsafe_var,'Ro',{'try',{10,19}}}},
{{15,32},erl_lint,{unsafe_var,'Class',{'try',{10,19}}}},
{{15,38},erl_lint,{unsafe_var,'Data',{'try',{10,19}}}},
{{21,38},erl_lint,{unsafe_var,'R',{'try',{18,19}}}},
{{21,40},erl_lint,{unbound_var,'RR',"R"}},
{{21,40},erl_lint,{unbound_var,'RR','R'}},
{{23,27},erl_lint,{unsafe_var,'R',{'try',{18,19}}}},
{{23,29},erl_lint,{unsafe_var,'RR',{'try',{18,19}}}},
{{23,32},erl_lint,{unsafe_var,'Class',{'try',{18,19}}}},
Expand All @@ -1526,8 +1526,8 @@ unsafe_vars_try(Config) when is_list(Config) ->
">>,
[],
{errors,[{{6,41},erl_lint,{unsafe_var,'R',{'try',{3,19}}}},
{{6,43},erl_lint,{unbound_var,'RR',"R"}},
{{6,46},erl_lint,{unbound_var,'Ro',"R"}},
{{6,43},erl_lint,{unbound_var,'RR','R'}},
{{6,46},erl_lint,{unbound_var,'Ro','R'}},
{{8,27},erl_lint,{unsafe_var,'R',{'try',{3,19}}}},
{{8,29},erl_lint,{unsafe_var,'RR',{'try',{3,19}}}},
{{8,32},erl_lint,{unsafe_var,'Ro',{'try',{3,19}}}},
Expand Down Expand Up @@ -1955,11 +1955,11 @@ otp_4988(Config) when is_list(Config) ->
{A}.
">>,
[],
{errors,[{{1,22},erl_lint,{bad_inline,{1,foo}}},
{{1,22},erl_lint,{bad_inline,{f,3}}},
{{1,22},erl_lint,{bad_inline,{f,4}}},
{{1,22},erl_lint,{bad_inline,{f,a}}},
{{3,16},erl_lint,{bad_inline,{g,12}}}],
{errors,[{{1,22},erl_lint,{bad_inline,{1,foo}}},
{{1,22},erl_lint,{bad_inline,{f,3},{f,[2]}}},
{{1,22},erl_lint,{bad_inline,{f,4},{f,[2]}}},
{{1,22},erl_lint,{bad_inline,{f,a},{f,[2]}}},
{{3,16},erl_lint,{bad_inline,{g,12},{g,[1]}}}],
[]}}],
[] = run(Config, Ts),
ok.
Expand Down Expand Up @@ -2308,10 +2308,10 @@ otp_5362(Config) when is_list(Config) ->
ok.
">>,
{[warn_unused_vars, warn_unused_import]},
{error,[{{5,15},erl_lint,{bad_inline,{inl,7}}},
{{6,15},erl_lint,{bad_inline,{inl,17}}},
{{11,18},erl_lint,{undefined_function,{fipp,0},"foop"}},
{{22,15},erl_lint,{bad_nowarn_unused_function,{and_not_used,2}}}],
{error,[{{5,15},erl_lint,{bad_inline,{inl,7},{inl,[1]}}},
{{6,15},erl_lint,{bad_inline,{inl,17},{inl,[1]}}},
{{11,18},erl_lint,{undefined_function,{fipp,0},{foop,[0]}}},
{{22,15},erl_lint,{bad_nowarn_unused_function,{and_not_used,2},{and_not_used,[1]}}}],
[{{3,15},erl_lint,{unused_import,{{b,1},lists}}},
{{9,14},erl_lint,{unused_function,{foop,0}}},
{{19,14},erl_lint,{unused_function,{not_used,0}}},
Expand Down Expand Up @@ -2403,7 +2403,7 @@ otp_5362(Config) when is_list(Config) ->
{[nowarn_unused_function]},
{errors,[{{3,16},erl_lint,disallowed_nowarn_bif_clash},
{{4,16},erl_lint,disallowed_nowarn_bif_clash},
{{4,16},erl_lint,{bad_nowarn_bif_clash,{spawn,2}}}],
{{4,16},erl_lint,{bad_nowarn_bif_clash,{spawn,2},{spawn,[1]}}}],
[]}
},

Expand Down Expand Up @@ -3077,7 +3077,7 @@ otp_11254(Config) when is_list(Config) ->
manifest(Module, Name) ->
fun Module:Nine/1.
">>,
{error,[{{4,26},erl_lint,{unbound_var,'Nine',"Name"}}],
{error,[{{4,26},erl_lint,{unbound_var,'Nine','Name'}}],
[{{3,30},erl_lint,{unused_var,'Name'}}]} =
run_test2(Config, Ts, []),
ok.
Expand Down Expand Up @@ -5439,26 +5439,29 @@ messages_with_jaro_suggestions(Config) ->
<<"-on_load(foa/0).
foo() -> ok.">>,
{[]},
{error,[{{1,22},erl_lint,{undefined_on_load,{foa,0},"foo"}}],
{error,[{{1,22},erl_lint,{undefined_on_load,{foa,0},foo}}],
[{{2,15},erl_lint,{unused_function,{foo,0}}}]}},
{undefined_nif,
<<"-export([foo/1]).
-nifs([foa/1]).
<<"-export([foo/1,bar/2]).
-nifs([foa/1,bar/1]).
-on_load(init/0).
init() ->
ok = erlang:load_nif(\"./example_nif\", 0).
foo(_X) ->
erlang:nif_error(nif_library_not_loaded).
bar(_X,_Y) ->
erlang:nif_error(nif_library_not_loaded).">>,
{[]},
{errors,[{{2,16},erl_lint,{undefined_nif,{foa,1},"foo"}}],[]}},
{errors,[{{2,16},erl_lint,{undefined_nif,{bar,1},{bar,[2]}}},
{{2,16},erl_lint,{undefined_nif,{foa,1},{foo,[1]}}}],[]}},
{record_and_field,
<<"-record(meep, { moo, muu }).
t(State) ->
Var = State#meep.mo,
State#mee{ moo = Var }.">>,
{[]},
{error,[{{3,36},erl_lint,{undefined_field,meep,mo,"moo"}},
{{4,24},erl_lint,{undefined_record,mee,"meep"}}],
{error,[{{3,36},erl_lint,{undefined_field,meep,mo,moo}},
{{4,24},erl_lint,{undefined_record,mee,meep}}],
[{{2,15},erl_lint,{unused_function,{t,1}}},
{{3,19},erl_lint,{unused_var,'Var'}}]}},
{unbound_var,
Expand All @@ -5467,27 +5470,44 @@ messages_with_jaro_suggestions(Config) ->
Var = State#meep.moo,
Stat#meep{ moo = Var }.">>,
{[]},
{error,[{{4,19},erl_lint,{unbound_var,'Stat',"State"}}],
{error,[{{4,19},erl_lint,{unbound_var,'Stat','State'}}],
[{{2,15},erl_lint,{unused_function,{t,1}}}]}},
{undefined_fun,
<<"-export([bar/1]).
baz(X) -> X.">>,
<<"-export([bar/1,foo/2]).
baz(X) -> X.
foo(X) -> X.
foo(X, Y, Z) -> X + Y + Z.">>,
{[]},
{error,[{{1,22},erl_lint,{undefined_function,{bar,1},"baz"}}],
[{{2,15},erl_lint,{unused_function,{baz,1}}}]}},
{error,[{{1,22},erl_lint,{undefined_function,{bar,1},{baz,[1]}}},
{{1,22},erl_lint,{undefined_function,{foo,2},{foo,[1,3]}}}],
[{{2,15},erl_lint,{unused_function,{baz,1}}},
{{3,15},erl_lint,{unused_function,{foo,1}}},
{{4,15},erl_lint,{unused_function,{foo,3}}}]}},
{nowarn_undefined_fun,
<<"-compile({nowarn_unused_function,[{an_not_used,1}]}).
and_not_used(_) -> foo.">>,
{[]},
{error,[{{1,22}, erl_lint,
{bad_nowarn_unused_function,{an_not_used,1},"and_not_used"}}],
{bad_nowarn_unused_function,{an_not_used,1},{and_not_used,[1]}}}],
[{{2,15},erl_lint,{unused_function,{and_not_used,1}}}]}},
{bad_inline,
<<"-compile({inline, {go,1}}).
gi(A) -> {A}.">>,
<<"-compile({inline, [{foo,1},{ba,1}]}).
foa(A) -> {A}.
ba(A, A) -> [A].">>,
{[]},
{error,[{{1,22},erl_lint,{bad_inline,{go,1},"gi"}}],
[{{2,15},erl_lint,{unused_function,{gi,1}}}]}}
{error,[{{1,22},erl_lint,{bad_inline,{ba,1},{ba,[2]}}},
{{1,22},erl_lint,{bad_inline,{foo,1},{foa,[1]}}}],
[{{2,15},erl_lint,{unused_function,{foa,1}}},
{{3,15},erl_lint,{unused_function,{ba,2}}}]}},
{bad_dialyzer_attribute,
<<"-dialyzer({nowarn_function,[foo/2,bar/1]}).
foo(X, Y, Z) -> X + Y + Z.
baz(A) -> A.">>,
{[]},
{error,[{{1,22},erl_lint,{undefined_function,{bar,1},{baz,[1]}}},
{{1,22},erl_lint,{undefined_function,{foo,2},{foo,[3]}}}],
[{{2,17},erl_lint,{unused_function,{foo,3}}},
{{3,17},erl_lint,{unused_function,{baz,1}}}]}}
],
[] = run(Config, Ts),

Expand Down

0 comments on commit 4b67a69

Please sign in to comment.