Skip to content

Commit

Permalink
erl_lint: The checks for "old bifs" are no longer required
Browse files Browse the repository at this point in the history
This makes uses of local functions whose names conflict with auto-imported
BIFs (without a no_auto_import declaration to resolve the conflict) always
be a warning, never an error. Previously, this was an error for "old"
BIfs (those that were auto imported pre OTP R14).
  • Loading branch information
richcarl committed Jan 15, 2025
1 parent 8fb9f1f commit e88ee26
Show file tree
Hide file tree
Showing 4 changed files with 21 additions and 173 deletions.
8 changes: 4 additions & 4 deletions lib/compiler/test/error_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -64,8 +64,8 @@ bif_clashes(Config) when is_list(Config) ->
erlang:length(X).
">>,
[return_warnings],
{error,
[{{4,18}, erl_lint,{call_to_redefined_old_bif,{length,1}}}], []} }],
{warning,
[{{4,18}, erl_lint,{call_to_redefined_bif,{length,1}}}]} }],
[] = run(Config, Ts),
Ts1 = [{bif_clashes2,
<<"
Expand All @@ -75,8 +75,8 @@ bif_clashes(Config) when is_list(Config) ->
length([a,b,c]).
">>,
[return_warnings],
{error,
[{{3,16}, erl_lint,{redefine_old_bif_import,{length,1}}}], []} }],
{warning,
[{{3,16}, erl_lint,{redefine_bif_import,{length,1}}}]} }],
[] = run(Config, Ts1),
Ts00 = [{bif_clashes3,
<<"
Expand Down
132 changes: 1 addition & 131 deletions lib/stdlib/src/erl_internal.erl
Original file line number Diff line number Diff line change
Expand Up @@ -55,7 +55,7 @@ of interest to programmers who manipulate Erlang code.
%%

-export([bif/2,bif/3,guard_bif/2,
type_test/2,new_type_test/2,old_type_test/2,old_bif/2]).
type_test/2,new_type_test/2,old_type_test/2]).
-export([arith_op/2,bool_op/2,comp_op/2,list_op/2,send_op/2,op_type/2]).

-export([is_type/2]).
Expand Down Expand Up @@ -450,136 +450,6 @@ bif(unregister, 1) -> true;
bif(whereis, 1) -> true;
bif(Name, A) when is_atom(Name), is_integer(A) -> false.

-doc false.
-spec old_bif(Name::atom(), Arity::arity()) -> boolean().
%% Returns true if erlang:Name/Arity is an old (pre R14) auto-imported BIF, false otherwise.
%% Use erlang:is_bultin(Mod, Name, Arity) to find whether a function is a BIF
%% (meaning implemented in C) or not.

old_bif(abs, 1) -> true;
old_bif(apply, 2) -> true;
old_bif(apply, 3) -> true;
old_bif(atom_to_binary, 2) -> true;
old_bif(atom_to_list, 1) -> true;
old_bif(binary_to_atom, 2) -> true;
old_bif(binary_to_existing_atom, 2) -> true;
old_bif(binary_to_list, 1) -> true;
old_bif(binary_to_list, 3) -> true;
old_bif(binary_to_term, 1) -> true;
old_bif(bitsize, 1) -> true;
old_bif(bit_size, 1) -> true;
old_bif(bitstring_to_list, 1) -> true;
old_bif(byte_size, 1) -> true;
old_bif(check_process_code, 2) -> true;
old_bif(date, 0) -> true;
old_bif(delete_module, 1) -> true;
old_bif(disconnect_node, 1) -> true;
old_bif(element, 2) -> true;
old_bif(erase, 0) -> true;
old_bif(erase, 1) -> true;
old_bif(exit, 1) -> true;
old_bif(exit, 2) -> true;
old_bif(float, 1) -> true;
old_bif(float_to_list, 1) -> true;
old_bif(garbage_collect, 0) -> true;
old_bif(garbage_collect, 1) -> true;
old_bif(get, 0) -> true;
old_bif(get, 1) -> true;
old_bif(get_keys, 1) -> true;
old_bif(group_leader, 0) -> true;
old_bif(group_leader, 2) -> true;
old_bif(halt, 0) -> true;
old_bif(halt, 1) -> true;
old_bif(hd, 1) -> true;
old_bif(integer_to_list, 1) -> true;
old_bif(iolist_size, 1) -> true;
old_bif(iolist_to_binary, 1) -> true;
old_bif(is_alive, 0) -> true;
old_bif(is_process_alive, 1) -> true;
old_bif(is_atom, 1) -> true;
old_bif(is_boolean, 1) -> true;
old_bif(is_binary, 1) -> true;
old_bif(is_bitstring, 1) -> true;
old_bif(is_float, 1) -> true;
old_bif(is_function, 1) -> true;
old_bif(is_function, 2) -> true;
old_bif(is_integer, 1) -> true;
old_bif(is_list, 1) -> true;
old_bif(is_number, 1) -> true;
old_bif(is_pid, 1) -> true;
old_bif(is_port, 1) -> true;
old_bif(is_reference, 1) -> true;
old_bif(is_tuple, 1) -> true;
old_bif(is_record, 2) -> true;
old_bif(is_record, 3) -> true;
old_bif(length, 1) -> true;
old_bif(link, 1) -> true;
old_bif(list_to_atom, 1) -> true;
old_bif(list_to_binary, 1) -> true;
old_bif(list_to_bitstring, 1) -> true;
old_bif(list_to_existing_atom, 1) -> true;
old_bif(list_to_float, 1) -> true;
old_bif(list_to_integer, 1) -> true;
old_bif(list_to_pid, 1) -> true;
old_bif(list_to_tuple, 1) -> true;
old_bif(load_module, 2) -> true;
old_bif(make_ref, 0) -> true;
old_bif(module_loaded, 1) -> true;
old_bif(monitor_node, 2) -> true;
old_bif(node, 0) -> true;
old_bif(node, 1) -> true;
old_bif(nodes, 0) -> true;
old_bif(nodes, 1) -> true;
old_bif(now, 0) -> true;
old_bif(open_port, 2) -> true;
old_bif(pid_to_list, 1) -> true;
old_bif(port_close, 1) -> true;
old_bif(port_command, 2) -> true;
old_bif(port_connect, 2) -> true;
old_bif(port_control, 3) -> true;
old_bif(pre_loaded, 0) -> true;
old_bif(process_flag, 2) -> true;
old_bif(process_flag, 3) -> true;
old_bif(process_info, 1) -> true;
old_bif(process_info, 2) -> true;
old_bif(processes, 0) -> true;
old_bif(purge_module, 1) -> true;
old_bif(put, 2) -> true;
old_bif(register, 2) -> true;
old_bif(registered, 0) -> true;
old_bif(round, 1) -> true;
old_bif(self, 0) -> true;
old_bif(setelement, 3) -> true;
old_bif(size, 1) -> true;
old_bif(spawn, 1) -> true;
old_bif(spawn, 2) -> true;
old_bif(spawn, 3) -> true;
old_bif(spawn, 4) -> true;
old_bif(spawn_link, 1) -> true;
old_bif(spawn_link, 2) -> true;
old_bif(spawn_link, 3) -> true;
old_bif(spawn_link, 4) -> true;
old_bif(spawn_monitor, 1) -> true;
old_bif(spawn_monitor, 3) -> true;
old_bif(spawn_opt, 2) -> true;
old_bif(spawn_opt, 3) -> true;
old_bif(spawn_opt, 4) -> true;
old_bif(spawn_opt, 5) -> true;
old_bif(split_binary, 2) -> true;
old_bif(statistics, 1) -> true;
old_bif(term_to_binary, 1) -> true;
old_bif(term_to_binary, 2) -> true;
old_bif(throw, 1) -> true;
old_bif(time, 0) -> true;
old_bif(tl, 1) -> true;
old_bif(trunc, 1) -> true;
old_bif(tuple_size, 1) -> true;
old_bif(tuple_to_list, 1) -> true;
old_bif(unlink, 1) -> true;
old_bif(unregister, 1) -> true;
old_bif(whereis, 1) -> true;
old_bif(Name, A) when is_atom(Name), is_integer(A) -> false.

-doc false.
-spec is_type(Name, NumberOfTypeVariables) -> boolean() when
Name :: atom(),
Expand Down
27 changes: 1 addition & 26 deletions lib/stdlib/src/erl_lint.erl
Original file line number Diff line number Diff line change
Expand Up @@ -357,16 +357,6 @@ format_error_1({call_to_redefined_bif,{F,A}}) ->
ambiguous call of overridden auto-imported BIF ~w/~w --
use erlang:~w/~w or "-compile({no_auto_import,[~w/~w]})." to resolve name clash
""", [F,A,F,A,F,A]};
format_error_1({call_to_redefined_old_bif,{F,A}}) ->
{~"""
ambiguous call of overridden pre Erlang/OTP R14 auto-imported BIF ~w/~w --
use erlang:~w/~w or \"-compile({no_auto_import,[~w/~w]}).\" to resolve name clash
""", [F,A,F,A,F,A]};
format_error_1({redefine_old_bif_import,{F,A}}) ->
{~"""
import directive overrides pre Erlang/OTP R14 auto-imported BIF ~w/~w --
use "-compile({no_auto_import,[~w/~w]})." to resolve name clash
""", [F,A,F,A]};
format_error_1({redefine_bif_import,{F,A}}) ->
{~"""
import directive overrides auto-imported BIF ~w/~w --
Expand Down Expand Up @@ -1830,13 +1820,7 @@ import(Anno, {Mod,Fs}, St00) ->
Warn = is_warn_enabled(bif_clash, St0) andalso
(not bif_clash_specifically_disabled(St0,{F,A})),
AutoImpSup = is_autoimport_suppressed(St0#lint.no_auto,{F,A}),
OldBif = erl_internal:old_bif(F,A),
{Err,if
Warn and (not AutoImpSup) and OldBif ->
add_error
(Anno,
{redefine_old_bif_import, {F,A}},
St0);
Warn and (not AutoImpSup) ->
add_warning
(Anno,
Expand Down Expand Up @@ -2910,16 +2894,7 @@ check_call(Anno, F, As, _Aa, St0) ->
false ?= AutoSuppressed,
true ?= is_warn_enabled(bif_clash, St0),
false ?= bif_clash_specifically_disabled(St0, {F,A}),
case erl_internal:old_bif(F, A) of
true ->
add_error(Anno,
{call_to_redefined_old_bif, {F,A}},
St0);
false ->
add_warning(Anno,
{call_to_redefined_bif, {F,A}},
St0)
end
add_warning(Anno, {call_to_redefined_bif, {F,A}}, St0)
else
_ ->
St0
Expand Down
27 changes: 15 additions & 12 deletions lib/stdlib/test/erl_lint_SUITE.erl
Original file line number Diff line number Diff line change
Expand Up @@ -2416,12 +2416,12 @@ otp_5362(Config) when is_list(Config) ->
">>,
{[nowarn_unused_function,
warn_deprecated_function]},
{error,
[{{5,19},erl_lint,{call_to_redefined_old_bif,{spawn,1}}}],
{warnings,
[{{4,19},erl_lint,{deprecated,{erlang,now,0},
"see the \"Time and Time Correction in Erlang\" "
"chapter of the ERTS User's Guide for more "
"information"}}]}},
"information"}},
{{5,19},erl_lint,{call_to_redefined_bif,{spawn,1}}}]}},
{otp_5362_5,
<<"-compile(nowarn_deprecated_function).
-compile(nowarn_bif_clash).
Expand Down Expand Up @@ -3250,7 +3250,7 @@ bif_clash(Config) when is_list(Config) ->
N.
">>,
[nowarn_unexported_function],
{errors,[{{2,19},erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}},
{warnings,[{{2,19},erl_lint,{call_to_redefined_bif,{size,1}}}]}},

%% Verify that warnings cannot be turned off in the old way.
{clash2,
Expand Down Expand Up @@ -3279,7 +3279,7 @@ bif_clash(Config) when is_list(Config) ->
">>,
[],
[]},
%% But this is totally wrong - meaning of the program changed in R14, so this is an error
%% For a pre R14 bif, it used to be an error, but is now a warning
{clash4,
<<"-export([size/1]).
size({N,_}) ->
Expand All @@ -3288,27 +3288,30 @@ bif_clash(Config) when is_list(Config) ->
size(X).
">>,
[],
{errors,[{{5,17},erl_lint,{call_to_redefined_old_bif,{size,1}}}],[]}},
%% For a post R14 bif, its only a warning
{warnings,[{{5,17},erl_lint,{call_to_redefined_bif,{size,1}}}]}},
%% For a post R14 bif, its only a warning; also check symbolic funs
{clash5,
<<"-export([binary_part/2]).
<<"-export([binary_part/2,f/0]).
binary_part({B,_},{X,Y}) ->
binary_part(B,{X,Y});
binary_part(B,{X,Y}) ->
binary:part(B,X,Y).
f() -> fun binary_part/2.
">>,
[],
{warnings,[{{3,17},erl_lint,{call_to_redefined_bif,{binary_part,2}}}]}},
{warnings,[{{3,17},erl_lint,{call_to_redefined_bif,{binary_part,2}}},
{{6,22},erl_lint,{call_to_redefined_bif,{binary_part,2}}}]}},
%% If you really mean to call yourself here, you can "unimport" size/1
{clash6,
<<"-export([size/1]).
<<"-export([size/1,f/0]).
-compile({no_auto_import,[size/1]}).
size([]) ->
0;
size({N,_}) ->
N;
size([_|T]) ->
1+size(T).
f() -> fun size/1.
">>,
[],
[]},
Expand Down Expand Up @@ -3394,15 +3397,15 @@ bif_clash(Config) when is_list(Config) ->
">>,
[],
[]},
%% Import directive clashing with old bif is an error, regardless of if it's called or not
%% Import directive clashing with old bif used to be an error, now a warning
{clash15,
<<"-export([x/1]).
-import(x,[abs/1]).
x(X) ->
binary_part(X,{1,2}).
">>,
[],
{errors,[{{2,16},erl_lint,{redefine_old_bif_import,{abs,1}}}],[]}},
{warnings,[{{2,16},erl_lint,{redefine_bif_import,{abs,1}}}]}},
%% For a new BIF, it's only a warning
{clash16,
<<"-export([x/1]).
Expand Down

0 comments on commit e88ee26

Please sign in to comment.