File 2932-erl_lint-Support-marking-previously-exported-functio.patch of Package erlang
From 8af32b6f27daefa1f2c4544c05685731c2e8eeaf Mon Sep 17 00:00:00 2001
From: =?UTF-8?q?John=20H=C3=B6gberg?= <john@erlang.org>
Date: Wed, 29 Jan 2020 15:53:27 +0100
Subject: [PATCH 2/2] erl_lint: Support marking previously exported functions
as removed
This mirrors -deprecated() and is a step towards removing the central
'otp_internal' module currently used for deprecation and removal
warnings.
---
lib/stdlib/src/erl_lint.erl | 68 +++++++++++++++++++++++++++++++++++++-
lib/stdlib/test/erl_lint_SUITE.erl | 28 ++++++++++++++--
2 files changed, 93 insertions(+), 3 deletions(-)
diff --git a/lib/stdlib/src/erl_lint.erl b/lib/stdlib/src/erl_lint.erl
index 8ce73a8f84..4dd30019d9 100644
--- a/lib/stdlib/src/erl_lint.erl
+++ b/lib/stdlib/src/erl_lint.erl
@@ -183,6 +183,14 @@ format_error({invalid_deprecated,D}) ->
format_error({bad_deprecated,{F,A}}) ->
io_lib:format("deprecated function ~tw/~w undefined or not exported",
[F,A]);
+format_error({invalid_removed,D}) ->
+ io_lib:format("badly formed removed attribute ~tw", [D]);
+format_error({bad_removed,{F,A}}) when F =:= '_'; A =:= '_' ->
+ io_lib:format("at least one function matching ~tw/~w is still exported",
+ [F,A]);
+format_error({bad_removed,{F,A}}) ->
+ io_lib:format("removed function ~tw/~w is still exported",
+ [F,A]);
format_error({bad_nowarn_unused_function,{F,A}}) ->
io_lib:format("function ~tw/~w undefined", [F,A]);
format_error({bad_nowarn_bif_clash,{F,A}}) ->
@@ -918,7 +926,8 @@ post_traversal_check(Forms, St0) ->
StE = check_unused_records(Forms, StD),
StF = check_local_opaque_types(StE),
StG = check_dialyzer_attribute(Forms, StF),
- check_callback_information(StG).
+ StH = check_callback_information(StG),
+ check_removed(Forms, StH).
%% check_behaviour(State0) -> State
%% Check that the behaviour attribute is valid.
@@ -1080,6 +1089,63 @@ deprecated_desc([Char | Str]) when is_integer(Char) -> deprecated_desc(Str);
deprecated_desc([]) -> true;
deprecated_desc(_) -> false.
+%% check_removed(Forms, State0) -> State
+
+check_removed(Forms, St0) ->
+ %% Get the correct list of exported functions.
+ Exports = case member(export_all, St0#lint.compile) of
+ true -> St0#lint.defined;
+ false -> St0#lint.exports
+ end,
+ X = gb_sets:to_list(Exports),
+ #lint{module = Mod} = St0,
+ Bad = [{E,L} || {attribute, L, removed, Removed} <- Forms,
+ R <- lists:flatten([Removed]),
+ E <- removed_cat(R, X, Mod)],
+ foldl(fun ({E,L}, St1) ->
+ add_error(L, E, St1)
+ end, St0, Bad).
+
+removed_cat({F, A, Desc}=R, X, Mod) ->
+ case removed_desc(Desc) of
+ false -> [{invalid_removed,R}];
+ true -> removed_fa(F, A, X, Mod)
+ end;
+removed_cat({F, A}, X, Mod) ->
+ removed_fa(F, A, X, Mod);
+removed_cat(module, X, Mod) ->
+ removed_fa('_', '_', X, Mod);
+removed_cat(R, _X, _Mod) ->
+ [{invalid_removed,R}].
+
+removed_fa('_', '_', X, _Mod) ->
+ case X of
+ [_|_] -> [{bad_removed,{'_','_'}}];
+ [] -> []
+ end;
+removed_fa(F, '_', X, _Mod) when is_atom(F) ->
+ %% Don't use this syntax for built-in functions.
+ case lists:filter(fun({F1,_}) -> F1 =:= F end, X) of
+ [_|_] -> [{bad_removed,{F,'_'}}];
+ _ -> []
+ end;
+removed_fa(F, A, X, Mod) when is_atom(F), is_integer(A), A >= 0 ->
+ case lists:member({F,A}, X) of
+ true ->
+ [{bad_removed,{F,A}}];
+ false ->
+ case erlang:is_builtin(Mod, F, A) of
+ true -> [{bad_removed,{F,A}}];
+ false -> []
+ end
+ end;
+removed_fa(F, A, _X, _Mod) ->
+ [{invalid_removed,{F,A}}].
+
+removed_desc([Char | Str]) when is_integer(Char) -> removed_desc(Str);
+removed_desc([]) -> true;
+removed_desc(_) -> false.
+
%% check_imports(Forms, State0) -> State
check_imports(Forms, St0) ->
diff --git a/lib/stdlib/test/erl_lint_SUITE.erl b/lib/stdlib/test/erl_lint_SUITE.erl
index 38d07249fd..a5de033e89 100644
--- a/lib/stdlib/test/erl_lint_SUITE.erl
+++ b/lib/stdlib/test/erl_lint_SUITE.erl
@@ -69,7 +69,7 @@
stacktrace_syntax/1,
otp_14285/1, otp_14378/1,
external_funs/1,otp_15563/1,
- unused_type/1, otp_16516/1,
+ unused_type/1,removed/1, otp_16516/1,
warn_missing_spec/1]).
suite() ->
@@ -92,7 +92,7 @@ all() ->
otp_11851, otp_11879, otp_13230,
record_errors, otp_11879_cont, non_latin1_module, otp_14323,
stacktrace_syntax, otp_14285, otp_14378, external_funs,
- otp_15563, unused_type, otp_16516,
+ otp_15563, unused_type, removed, otp_16516,
warn_missing_spec].
groups() ->
@@ -4343,6 +4343,30 @@ otp_15563(Config) when is_list(Config) ->
{5,erl_lint,{unused_var,'V2'}}]}}],
[] = run(Config, Ts).
+removed(Config) when is_list(Config) ->
+ Ts = [{removed,
+ <<"-removed([{nonexistent,1,\"hi\"}]). %% okay since it doesn't exist
+ -removed([frutt/0]). %% okay since frutt/0 is not exported
+ -removed([t/0]). %% not okay since t/0 is exported
+ -removed([{t,'_'}]). %% not okay since t/0 is exported
+ -removed([{'_','_'}]). %% not okay since t/0 is exported
+ -removed([{{badly,formed},1}]).
+ -removed('badly formed').
+ -export([t/0]).
+ frutt() -> ok.
+ t() -> ok.
+ ">>,
+ {[]},
+ {error,[{3,erl_lint,{bad_removed,{t,0}}},
+ {4,erl_lint,{bad_removed,{t,'_'}}},
+ {5,erl_lint,{bad_removed,{'_','_'}}},
+ {6,erl_lint,{invalid_removed,{{badly,formed},1}}},
+ {7,erl_lint,{invalid_removed,'badly formed'}}],
+ [{9,erl_lint,{unused_function,{frutt,0}}}]}}
+ ],
+ [] = run(Config, Ts),
+ ok.
+
warn_missing_spec(Config) ->
Test = <<"-export([external_with_spec/0, external_no_spec/0]).
--
2.16.4