From 634dd378030292abeec98e7f332e57c5d36e13ef Mon Sep 17 00:00:00 2001 From: Patrik Nyblom Date: Wed, 26 May 2010 12:22:50 +0200 Subject: Return nowarn_bif_clash functionality but with warning Wrote and changed some tests in stdlib:erl_lint_SUITE nowarn_bif_clash is obsoleted but will remove warnings and errors about bif clashes. The recommended way is to use no_auto_import directives instead. Hopefully erlang.erl is the only user in the world of nowarn_bif_clash. --- lib/stdlib/src/erl_lint.erl | 133 +++++++++++++++++++++++++++++++------------- 1 file changed, 95 insertions(+), 38 deletions(-) (limited to 'lib/stdlib/src') diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl index acb9165ead..631ad0c1e3 100644 --- a/lib/stdlib/src/erl_lint.erl +++ b/lib/stdlib/src/erl_lint.erl @@ -163,6 +163,9 @@ format_error({bad_nowarn_unused_function,{F,A}}) -> io_lib:format("function ~w/~w undefined", [F,A]); format_error({bad_nowarn_bif_clash,{F,A}}) -> io_lib:format("function ~w/~w undefined", [F,A]); +format_error(deprecated_nowarn_bif_clash) -> + io_lib:format("compile directive nowarn_bif_clash is deprecated,~n" + " - use explicit module names or -compile({no_auto_import, [F/A]})", []); format_error({bad_nowarn_deprecated_function,{M,F,A}}) -> io_lib:format("~w:~w/~w is not a deprecated function", [M,F,A]); format_error({bad_on_load,Term}) -> @@ -188,11 +191,11 @@ format_error({define_import,{F,A}}) -> io_lib:format("defining imported function ~w/~w", [F,A]); format_error({unused_function,{F,A}}) -> io_lib:format("function ~w/~w is unused", [F,A]); -format_error({redefine_bif,{F,A}}) -> +format_error({call_to_redefined_bif,{F,A}}) -> io_lib:format("ambiguous call of redefined auto-imported BIF ~w/~w~n" " - use erlang:~w/~w or \"-compile({no_auto_import,[~w/~w]}).\" " "to resolve name clash", [F,A,F,A,F,A]); -format_error({redefine_old_bif,{F,A}}) -> +format_error({call_to_redefined_old_bif,{F,A}}) -> io_lib:format("ambiguous call of redefined pre R14 auto-imported BIF ~w/~w~n" " - use erlang:~w/~w or \"-compile({no_auto_import,[~w/~w]}).\" " "to resolve name clash", [F,A,F,A,F,A]); @@ -549,9 +552,11 @@ loc(L) -> forms(Forms0, St0) -> Forms = eval_file_attribute(Forms0, St0), Locals = local_functions(Forms), - AutoImportSupressed = auto_import_supressed(St0#lint.compile), + AutoImportSuppressed = auto_import_suppressed(St0#lint.compile), + StDeprecated = deprecated_compile_flags(Forms,St0), %% Line numbers are from now on pairs {File,Line}. - St1 = includes_qlc_hrl(Forms, St0#lint{locals = Locals, no_auto = AutoImportSupressed}), + St1 = includes_qlc_hrl(Forms, StDeprecated#lint{locals = Locals, + no_auto = AutoImportSuppressed}), St2 = bif_clashes(Forms, St1), St3 = not_deprecated(Forms, St2), St4 = foldl(fun form/2, pre_scan(Forms, St3), Forms), @@ -757,6 +762,23 @@ not_deprecated(Forms, St0) -> St1 = func_line_warning(bad_nowarn_deprecated_function, Bad, St0), St1#lint{not_deprecated = ordsets:from_list(Nowarn)}. +deprecated_compile_flags(Forms, St0) -> + %% There are (still) no line numbers in St0#lint.compile. + Warnings0 = [ {St0#lint.file,{L,erl_lint,deprecated_nowarn_bif_clash}} || + {attribute,[{line,{_,L}}],compile,nowarn_bif_clash} <- Forms ], + Warnings1 = [ {St0#lint.file,{L,erl_lint,deprecated_nowarn_bif_clash}} || + {attribute,[{line,{_,L}}],compile,{nowarn_bif_clash, {_,_}}} <- Forms ], + Disabled = (not is_warn_enabled(bif_clash, St0)), + Warnings = if + Disabled andalso Warnings0 =:= [] -> + [{St0#lint.file,{erl_lint,deprecated_nowarn_bif_clash}} | St0#lint.warnings]; + Disabled -> + Warnings0 ++ Warnings1 ++ St0#lint.warnings; + true -> + Warnings1 ++ St0#lint.warnings + end, + St0#lint{warnings=Warnings}. + %% post_traversal_check(Forms, State0) -> State. %% Do some further checking after the forms have been traversed and %% data about calls etc. have been collected. @@ -1015,7 +1037,8 @@ check_option_functions(Forms, Tag0, Type, St0) -> {Tag, FAs0} <- lists:flatten([Args]), Tag0 =:= Tag, FA <- lists:flatten([FAs0])], - DefFunctions = gb_sets:to_list(St0#lint.defined) -- pseudolocals(), + DefFunctions = (gb_sets:to_list(St0#lint.defined) -- pseudolocals()) ++ + [{F,A} || {{F,A},_} <- orddict:to_list(St0#lint.imports)], Bad = [{FA,L} || {FA,L} <- FAsL, not member(FA, DefFunctions)], func_line_error(Type, Bad, St0). @@ -1108,8 +1131,10 @@ import(Line, {Mod,Fs}, St) -> Efs -> {Err, St1} = foldl(fun ({bif,{F,A},_}, {Err,St0}) -> - Warn = is_warn_enabled(bif_clash, St0), %% PaN -> import directive - AutoImpSup = is_autoimport_supressed(St0#lint.no_auto,{F,A}), + %% BifClash - import directive + Warn = is_warn_enabled(bif_clash, St0) + and (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 -> @@ -1123,7 +1148,7 @@ import(Line, {Mod,Fs}, St) -> {redefine_bif_import, {F,A}}, St0); true -> - St0 + St0 end}; (Ef, {_Err,St0}) -> {true,add_error(Line, @@ -1249,14 +1274,6 @@ define_function(Line, Name, Arity, St0) -> add_error(Line, {redefine_function,NA}, St1); false -> St2 = St1#lint{defined=gb_sets:add_element(NA, St1#lint.defined)}, -%% St = case erl_internal:bif(Name, Arity) andalso %% PaN - Function definitions -%% (not is_function_exported(Name, Arity, St2)) andalso -%% is_warn_enabled(bif_clash, St2) andalso -%% is_bif_clash(Name,Arity,St2) andalso -%% (not is_autoimport_supressed(St0#lint.no_auto,NA)) of -%% true -> add_warning(Line, {redefine_bif,NA}, St2); -%% false -> St2 -%% end, case imported(Name, Arity, St2) of {yes,_M} -> add_error(Line, {define_import,NA}, St2); no -> St2 @@ -1762,17 +1779,16 @@ gexpr({call,Line,{remote,_,{atom,_,erlang},{atom,_,is_record}=Isr},[_,_,_]=Args} gexpr({call,Line,{atom,_La,F},As}, Vt, St0) -> {Asvt,St1} = gexpr_list(As, Vt, St0), A = length(As), - case (not is_local_function(St1#lint.locals,{F,A})) andalso %% PaN -> Function called in guard - (not is_imported_function(St1#lint.imports,{F,A})) andalso - erl_internal:guard_bif(F, A) andalso - (not is_autoimport_supressed(St1#lint.no_auto, {F,A})) of + %% BifClash - Function called in guard + case erl_internal:guard_bif(F, A) andalso no_guard_bif_clash(St1,{F,A}) of true -> %% Also check that it is auto-imported. case erl_internal:bif(F, A) of true -> {Asvt,St1}; false -> {Asvt,add_error(Line, {explicit_export,F,A}, St1)} end; - false -> {Asvt,add_error(Line, illegal_guard_expr, St1)} + false -> + {Asvt,add_error(Line, illegal_guard_expr, St1)} end; gexpr({call,Line,{remote,_Lr,{atom,_Lm,erlang},{atom,_Lf,F}},As}, Vt, St0) -> {Asvt,St1} = gexpr_list(As, Vt, St0), @@ -1998,10 +2014,11 @@ expr({'fun',Line,Body}, Vt, St) -> {Bvt, St1} = fun_clauses(Cs, Vt, St), {vtupdate(Bvt, Vt), St1}; {function,F,A} -> + %% BifClash - Fun expression %% N.B. Only allows BIFs here as well, NO IMPORTS!! - case ((not is_local_function(St#lint.locals,{F,A})) andalso %% PaN - Fun expression + case ((not is_local_function(St#lint.locals,{F,A})) andalso (erl_internal:bif(F, A) andalso - (not is_autoimport_supressed(St#lint.no_auto,{F,A})))) of + (not is_autoimport_suppressed(St#lint.no_auto,{F,A})))) of true -> {[],St}; false -> {[],call_function(Line, F, A, St)} end; @@ -2036,8 +2053,9 @@ expr({call,Line,{atom,La,F},As}, Vt, St0) -> A = length(As), IsLocal = is_local_function(St2#lint.locals,{F,A}), IsAutoBif = erl_internal:bif(F, A), - AutoSupressed = is_autoimport_supressed(St2#lint.no_auto,{F,A}), - case ((not IsLocal) andalso IsAutoBif andalso (not AutoSupressed)) of %% PaN - function call + AutoSuppressed = is_autoimport_suppressed(St2#lint.no_auto,{F,A}), + Warn = is_warn_enabled(bif_clash, St2) and (not bif_clash_specifically_disabled(St2,{F,A})), + case ((not IsLocal) andalso IsAutoBif andalso (not AutoSuppressed)) of true -> St3 = deprecated_function(Line, erlang, F, As, St2), {Asvt,St3}; @@ -2052,27 +2070,33 @@ expr({call,Line,{atom,La,F},As}, Vt, St0) -> case {F,A} of {record_info,2} -> check_record_info_call(Line,La,As,St2); - N when N =:= St2#lint.func -> - St2; - _ -> + N -> + %% BifClash - function call + %% Issue these warnings/errors even if it's a recursive call St3 = if - (not AutoSupressed) andalso IsAutoBif -> + (not AutoSuppressed) andalso IsAutoBif andalso Warn -> case erl_internal:old_bif(F,A) of true -> add_error (Line, - {redefine_old_bif, {F,A}}, + {call_to_redefined_old_bif, {F,A}}, St2); false -> add_warning (Line, - {redefine_bif, {F,A}}, + {call_to_redefined_bif, {F,A}}, St2) end; true -> St2 end, - call_function(Line, F, A, St3) + %% ...but don't lint recursive calls + if + N =:= St3#lint.func -> + St3; + true -> + call_function(Line, F, A, St3) + end end end} end; @@ -3502,22 +3526,55 @@ expand_package(M, St0) -> end end. + +%% Prebuild set of local functions (to override auto-import) local_functions(Forms) -> gb_sets:from_list([ {Func,Arity} || {function,_,Func,Arity,_} <- Forms ]). - +%% Predicate to find out if the function is locally defined is_local_function(LocalSet,{Func,Arity}) -> gb_sets:is_element({Func,Arity},LocalSet). - +%% Predicate to see if a function is explicitly imported is_imported_function(ImportSet,{Func,Arity}) -> case orddict:find({Func,Arity}, ImportSet) of {ok,_Mod} -> true; error -> false end. - -auto_import_supressed(CompileFlags) -> +%% Predicate to see if a function is explicitly imported from the erlang module +is_imported_from_erlang(ImportSet,{Func,Arity}) -> + case orddict:find({Func,Arity}, ImportSet) of + {ok,erlang} -> true; + _ -> false + end. +%% Build set of functions where auto-import is explicitly supressed +auto_import_suppressed(CompileFlags) -> L0 = [ X || {no_auto_import,X} <- CompileFlags ], L1 = [ {Y,Z} || {Y,Z} <- lists:flatten(L0), is_atom(Y), is_integer(Z) ], gb_sets:from_list(L1). - -is_autoimport_supressed(NoAutoSet,{Func,Arity}) -> +%% Predicate to find out if autoimport is explicitly supressed for a function +is_autoimport_suppressed(NoAutoSet,{Func,Arity}) -> gb_sets:is_element({Func,Arity},NoAutoSet). +%% Predicate to find out if a function specific bif-clash supression (old deprecated) is present +bif_clash_specifically_disabled(St,{F,A}) -> + Nowarn = nowarn_function(nowarn_bif_clash, St#lint.compile), + lists:member({F,A},Nowarn). + +%% Predicate to find out if an autoimported guard_bif is not overriden in some way +%% Guard Bif without module name is disallowed if +%% * It is overridden by local function +%% * It is overridden by -import and that import is not of itself (i.e. from module erlang) +%% * The autoimport is suppressed or it's not reimported by -import directive +%% Otherwise it's OK (given that it's actually a guard bif and actually is autoimported) +no_guard_bif_clash(St,{F,A}) -> + ( + (not is_local_function(St#lint.locals,{F,A})) + andalso + ( + (not is_imported_function(St#lint.imports,{F,A})) orelse + is_imported_from_erlang(St#lint.imports,{F,A}) + ) + andalso + ( + (not is_autoimport_suppressed(St#lint.no_auto, {F,A})) orelse + is_imported_from_erlang(St#lint.imports,{F,A}) + ) + ). -- cgit v1.2.3